{-
   Gitea API

   This documentation describes the Gitea API.

   OpenAPI Version: 3.0.1
   Gitea API API version: 1.23.1
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Gitea.API.Settings
-}

{-# 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 Gitea.API.Settings where

import Gitea.Core
import Gitea.MimeTypes
import Gitea.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


-- ** Settings

-- *** getGeneralAPISettings

-- | @GET \/settings\/api@
-- 
-- Get instance's global settings for api
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getGeneralAPISettings
  :: GiteaRequest GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
getGeneralAPISettings :: GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
getGeneralAPISettings =
  Method
-> [ByteString]
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/settings/api"]
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest
  GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetGeneralAPISettings MimeNoContent GeneralAPISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

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


-- *** getGeneralAttachmentSettings

-- | @GET \/settings\/attachment@
-- 
-- Get instance's global settings for Attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getGeneralAttachmentSettings
  :: GiteaRequest GetGeneralAttachmentSettings MimeNoContent GeneralAttachmentSettings MimeJSON
getGeneralAttachmentSettings :: GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
getGeneralAttachmentSettings =
  Method
-> [ByteString]
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/settings/attachment"]
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest
  GetGeneralAttachmentSettings
  MimeNoContent
  GeneralAttachmentSettings
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetGeneralAttachmentSettings
     MimeNoContent
     GeneralAttachmentSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

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


-- *** getGeneralRepositorySettings

-- | @GET \/settings\/repository@
-- 
-- Get instance's global settings for repositories
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getGeneralRepositorySettings
  :: GiteaRequest GetGeneralRepositorySettings MimeNoContent GeneralRepoSettings MimeJSON
getGeneralRepositorySettings :: GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
getGeneralRepositorySettings =
  Method
-> [ByteString]
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/settings/repository"]
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest
  GetGeneralRepositorySettings
  MimeNoContent
  GeneralRepoSettings
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetGeneralRepositorySettings
     MimeNoContent
     GeneralRepoSettings
     MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

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


-- *** getGeneralUISettings

-- | @GET \/settings\/ui@
-- 
-- Get instance's global settings for ui
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getGeneralUISettings
  :: GiteaRequest GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
getGeneralUISettings :: GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
getGeneralUISettings =
  Method
-> [ByteString]
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/settings/ui"]
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest
  GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetGeneralUISettings MimeNoContent GeneralUISettings MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

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