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

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


-- ** Miscellaneous

-- *** getGitignoreTemplateInfo

-- | @GET \/gitignore\/templates\/{name}@
-- 
-- Returns information about a gitignore template
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getGitignoreTemplateInfo
  :: Name -- ^ "name" -  name of the template
  -> GiteaRequest GetGitignoreTemplateInfo MimeNoContent GitignoreTemplateInfo MimeJSON
getGitignoreTemplateInfo :: Name
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     MimeJSON
getGitignoreTemplateInfo (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/gitignore/templates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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
  GetGitignoreTemplateInfo
  MimeNoContent
  GitignoreTemplateInfo
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetGitignoreTemplateInfo
     MimeNoContent
     GitignoreTemplateInfo
     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 GetGitignoreTemplateInfo  
-- | @application/json@
instance Produces GetGitignoreTemplateInfo MimeJSON


-- *** getLabelTemplateInfo

-- | @GET \/label\/templates\/{name}@
-- 
-- Returns all labels in a template
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getLabelTemplateInfo
  :: Name -- ^ "name" -  name of the template
  -> GiteaRequest GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
getLabelTemplateInfo :: Name
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
getLabelTemplateInfo (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/label/templates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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
  GetLabelTemplateInfo MimeNoContent [LabelTemplate] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetLabelTemplateInfo MimeNoContent [LabelTemplate] 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 GetLabelTemplateInfo  
-- | @application/json@
instance Produces GetLabelTemplateInfo MimeJSON


-- *** getLicenseTemplateInfo

-- | @GET \/licenses\/{name}@
-- 
-- Returns information about a license template
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getLicenseTemplateInfo
  :: Name -- ^ "name" -  name of the license
  -> GiteaRequest GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
getLicenseTemplateInfo :: Name
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
getLicenseTemplateInfo (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/licenses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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
  GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetLicenseTemplateInfo MimeNoContent LicenseTemplateInfo 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 GetLicenseTemplateInfo  
-- | @application/json@
instance Produces GetLicenseTemplateInfo MimeJSON


-- *** getNodeInfo

-- | @GET \/nodeinfo@
-- 
-- Returns the nodeinfo of the Gitea application
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getNodeInfo
  :: GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
getNodeInfo :: GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
getNodeInfo =
  Method
-> [ByteString]
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/nodeinfo"]
    GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo  
-- | @application/json@
instance Produces GetNodeInfo MimeJSON


-- *** getSigningKey

-- | @GET \/signing-key.gpg@
-- 
-- Get default signing-key.gpg
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getSigningKey
  :: GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
getSigningKey :: GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
getSigningKey =
  Method
-> [ByteString]
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/signing-key.gpg"]
    GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
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 GetSigningKey  
-- | @text/plain@
instance Produces GetSigningKey MimePlainText


-- *** getVersion

-- | @GET \/version@
-- 
-- Returns the version of the Gitea application
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getVersion
  :: GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
getVersion :: GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
getVersion =
  Method
-> [ByteString]
-> GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/version"]
    GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion  
-- | @application/json@
instance Produces GetVersion MimeJSON


-- *** listGitignoresTemplates

-- | @GET \/gitignore\/templates@
-- 
-- Returns a list of all gitignore templates
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
listGitignoresTemplates
  :: GiteaRequest ListGitignoresTemplates MimeNoContent [Text] MimeJSON
listGitignoresTemplates :: GiteaRequest ListGitignoresTemplates MimeNoContent [Text] MimeJSON
listGitignoresTemplates =
  Method
-> [ByteString]
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/gitignore/templates"]
    GiteaRequest ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     ListGitignoresTemplates MimeNoContent [Text] 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 ListGitignoresTemplates  
-- | @application/json@
instance Produces ListGitignoresTemplates MimeJSON


-- *** listLabelTemplates

-- | @GET \/label\/templates@
-- 
-- Returns a list of all label templates
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
listLabelTemplates
  :: GiteaRequest ListLabelTemplates MimeNoContent [Text] MimeJSON
listLabelTemplates :: GiteaRequest ListLabelTemplates MimeNoContent [Text] MimeJSON
listLabelTemplates =
  Method
-> [ByteString]
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/label/templates"]
    GiteaRequest ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest ListLabelTemplates MimeNoContent [Text] 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 ListLabelTemplates  
-- | @application/json@
instance Produces ListLabelTemplates MimeJSON


-- *** listLicenseTemplates

-- | @GET \/licenses@
-- 
-- Returns a list of all license templates
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
listLicenseTemplates
  :: GiteaRequest ListLicenseTemplates MimeNoContent [LicensesTemplateListEntry] MimeJSON
listLicenseTemplates :: GiteaRequest
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
listLicenseTemplates =
  Method
-> [ByteString]
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/licenses"]
    GiteaRequest
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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
  ListLicenseTemplates
  MimeNoContent
  [LicensesTemplateListEntry]
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     ListLicenseTemplates
     MimeNoContent
     [LicensesTemplateListEntry]
     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 ListLicenseTemplates  
-- | @application/json@
instance Produces ListLicenseTemplates MimeJSON


-- *** renderMarkdown

-- | @POST \/markdown@
-- 
-- Render a markdown document as HTML
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
renderMarkdown
  :: (Consumes RenderMarkdown MimeJSON)
  => GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
renderMarkdown :: Consumes RenderMarkdown MimeJSON =>
GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
renderMarkdown =
  Method
-> [ByteString]
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/markdown"]
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
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 RenderMarkdown 
instance HasBodyParam RenderMarkdown MarkdownOption 

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

-- | @text/html@
instance Produces RenderMarkdown MimeTextHtml


-- *** renderMarkdownRaw

-- | @POST \/markdown\/raw@
-- 
-- Render raw markdown as HTML
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
renderMarkdownRaw
  :: (Consumes RenderMarkdownRaw MimePlainText, MimeRender MimePlainText Body)
  => Body -- ^ "body" -  Request body to render
  -> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
renderMarkdownRaw :: (Consumes RenderMarkdownRaw MimePlainText,
 MimeRender MimePlainText Body) =>
Body
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
renderMarkdownRaw Body
body =
  Method
-> [ByteString]
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/markdown/raw"]
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Body
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RenderMarkdownRaw contentType,
 MimeRender contentType Body) =>
GiteaRequest RenderMarkdownRaw contentType res accept
-> Body -> GiteaRequest RenderMarkdownRaw contentType res accept
`setBodyParam` Body
body

data RenderMarkdownRaw 

-- | /Body Param/ "body" - Request body to render
instance HasBodyParam RenderMarkdownRaw Body 

-- | @text/plain@
instance Consumes RenderMarkdownRaw MimePlainText

-- | @text/html@
instance Produces RenderMarkdownRaw MimeTextHtml


-- *** renderMarkup

-- | @POST \/markup@
-- 
-- Render a markup document as HTML
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
renderMarkup
  :: (Consumes RenderMarkup MimeJSON)
  => GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
renderMarkup :: Consumes RenderMarkup MimeJSON =>
GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
renderMarkup =
  Method
-> [ByteString]
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/markup"]
    GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyToken
-> GiteaRequest RenderMarkup MimeJSON Text MimeTextHtml
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 RenderMarkup 
instance HasBodyParam RenderMarkup MarkupOption 

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

-- | @text/html@
instance Produces RenderMarkup MimeTextHtml