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

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


-- ** Repository

-- *** acceptRepoTransfer

-- | @POST \/repos\/{owner}\/{repo}\/transfer\/accept@
-- 
-- Accept a repo transfer
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
acceptRepoTransfer
  :: Owner -- ^ "owner" -  owner of the repo to transfer
  -> Repo -- ^ "repo" -  name of the repo to transfer
  -> GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
acceptRepoTransfer :: Owner
-> Repo
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository MimeJSON
acceptRepoTransfer (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer/accept"]
    GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AcceptRepoTransfer MimeNoContent Repository 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 AcceptRepoTransfer  
-- | @application/json@
instance Produces AcceptRepoTransfer MimeJSON


-- *** createCurrentUserRepo

-- | @POST \/user\/repos@
-- 
-- Create a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
createCurrentUserRepo
  :: (Consumes CreateCurrentUserRepo MimeJSON)
  => GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
createCurrentUserRepo :: Consumes CreateCurrentUserRepo MimeJSON =>
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
createCurrentUserRepo =
  Method
-> [ByteString]
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/repos"]
    GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository 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 CreateCurrentUserRepo 
instance HasBodyParam CreateCurrentUserRepo CreateRepoOption 

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

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


-- *** createFork

-- | @POST \/repos\/{owner}\/{repo}\/forks@
-- 
-- Fork a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
createFork
  :: (Consumes CreateFork contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo to fork
  -> Repo -- ^ "repo" -  name of the repo to fork
  -> GiteaRequest CreateFork contentType Repository MimeJSON
createFork :: forall contentType.
Consumes CreateFork contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest CreateFork contentType Repository MimeJSON
createFork ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/forks"]
    GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateFork contentType Repository 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 CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateFork contentType Repository 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 CreateFork 
instance HasBodyParam CreateFork CreateForkOption 

-- | @application/json@
instance Consumes CreateFork MimeJSON
-- | @text/plain@
instance Consumes CreateFork MimePlainText

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


-- *** createRepoVariable

-- | @POST \/repos\/{owner}\/{repo}\/actions\/variables\/{variablename}@
-- 
-- Create a repo-level variable
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
createRepoVariable
  :: (Consumes CreateRepoVariable contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  name of the owner
  -> Repo -- ^ "repo" -  name of the repository
  -> Variablename -- ^ "variablename" -  name of the variable
  -> GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
createRepoVariable :: forall contentType.
Consumes CreateRepoVariable contentType =>
ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
createRepoVariable ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
  Method
-> [ByteString]
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
    GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     CreateRepoVariable contentType NoContent MimeNoContent
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 CreateRepoVariable 
instance HasBodyParam CreateRepoVariable CreateVariableOption 

-- | @application/json@
instance Consumes CreateRepoVariable MimeJSON
-- | @text/plain@
instance Consumes CreateRepoVariable MimePlainText

instance Produces CreateRepoVariable MimeNoContent


-- *** deleteRepoSecret

-- | @DELETE \/repos\/{owner}\/{repo}\/actions\/secrets\/{secretname}@
-- 
-- Delete a secret in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
deleteRepoSecret
  :: Owner -- ^ "owner" -  owner of the repository
  -> Repo -- ^ "repo" -  name of the repository
  -> Secretname -- ^ "secretname" -  name of the secret
  -> GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
deleteRepoSecret :: Owner
-> Repo
-> Secretname
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
deleteRepoSecret (Owner Text
owner) (Repo Text
repo) (Secretname Text
secretname) =
  Method
-> [ByteString]
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
    GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     DeleteRepoSecret MimeNoContent NoContent MimeNoContent
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 DeleteRepoSecret  
instance Produces DeleteRepoSecret MimeNoContent


-- *** deleteRepoVariable

-- | @DELETE \/repos\/{owner}\/{repo}\/actions\/variables\/{variablename}@
-- 
-- Delete a repo-level variable
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
deleteRepoVariable
  :: Owner -- ^ "owner" -  name of the owner
  -> Repo -- ^ "repo" -  name of the repository
  -> Variablename -- ^ "variablename" -  name of the variable
  -> GiteaRequest DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
deleteRepoVariable :: Owner
-> Repo
-> Variablename
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
deleteRepoVariable (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
  Method
-> [ByteString]
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
    GiteaRequest
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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
  DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     DeleteRepoVariable MimeNoContent ActionVariable 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 DeleteRepoVariable  
-- | @application/json@
instance Produces DeleteRepoVariable MimeJSON


-- *** generateRepo

-- | @POST \/repos\/{template_owner}\/{template_repo}\/generate@
-- 
-- Create a repository using a template
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
generateRepo
  :: (Consumes GenerateRepo MimeJSON)
  => TemplateOwner -- ^ "templateOwner" -  name of the template repository owner
  -> TemplateRepo -- ^ "templateRepo" -  name of the template repository
  -> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
generateRepo :: Consumes GenerateRepo MimeJSON =>
TemplateOwner
-> TemplateRepo
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
generateRepo (TemplateOwner Text
templateOwner) (TemplateRepo Text
templateRepo) =
  Method
-> [ByteString]
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
templateOwner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
templateRepo,ByteString
"/generate"]
    GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GenerateRepo MimeJSON Repository 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 GenerateRepo 
instance HasBodyParam GenerateRepo GenerateRepoOption 

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

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


-- *** getAnnotatedTag

-- | @GET \/repos\/{owner}\/{repo}\/git\/tags\/{sha}@
-- 
-- Gets the tag object of an annotated tag (not lightweight tags)
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getAnnotatedTag
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  sha of the tag. The Git tags API only supports annotated tag objects, not lightweight tags.
  -> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
getAnnotatedTag :: Owner
-> Repo
-> Sha
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
getAnnotatedTag (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag 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 GetAnnotatedTag  
-- | @application/json@
instance Produces GetAnnotatedTag MimeJSON


-- *** getBlob

-- | @GET \/repos\/{owner}\/{repo}\/git\/blobs\/{sha}@
-- 
-- Gets the blob of a repository.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getBlob
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  sha of the commit
  -> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
getBlob :: Owner
-> Repo
-> Sha
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
getBlob (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/blobs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse 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 GetBlob  
-- | @application/json@
instance Produces GetBlob MimeJSON


-- *** getRepoVariable

-- | @GET \/repos\/{owner}\/{repo}\/actions\/variables\/{variablename}@
-- 
-- Get a repo-level variable
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getRepoVariable
  :: Owner -- ^ "owner" -  name of the owner
  -> Repo -- ^ "repo" -  name of the repository
  -> Variablename -- ^ "variablename" -  name of the variable
  -> GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
getRepoVariable :: Owner
-> Repo
-> Variablename
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable MimeJSON
getRepoVariable (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
  Method
-> [ByteString]
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
    GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetRepoVariable MimeNoContent ActionVariable 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 GetRepoVariable  
-- | @application/json@
instance Produces GetRepoVariable MimeJSON


-- *** getRepoVariablesList

-- | @GET \/repos\/{owner}\/{repo}\/actions\/variables@
-- 
-- Get repo-level variables list
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getRepoVariablesList
  :: Owner -- ^ "owner" -  name of the owner
  -> Repo -- ^ "repo" -  name of the repository
  -> GiteaRequest GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
getRepoVariablesList :: Owner
-> Repo
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
getRepoVariablesList (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables"]
    GiteaRequest
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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
  GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     GetRepoVariablesList MimeNoContent [ActionVariable] 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 GetRepoVariablesList  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam GetRepoVariablesList Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest GetRepoVariablesList contentType res accept
-> Page -> GiteaRequest GetRepoVariablesList contentType res accept
applyOptionalParam GiteaRequest GetRepoVariablesList contentType res accept
req (Page Int
xs) =
    GiteaRequest GetRepoVariablesList contentType res accept
req GiteaRequest GetRepoVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetRepoVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam GetRepoVariablesList Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest GetRepoVariablesList contentType res accept
-> Limit
-> GiteaRequest GetRepoVariablesList contentType res accept
applyOptionalParam GiteaRequest GetRepoVariablesList contentType res accept
req (Limit Int
xs) =
    GiteaRequest GetRepoVariablesList contentType res accept
req GiteaRequest GetRepoVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetRepoVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces GetRepoVariablesList MimeJSON


-- *** getTree

-- | @GET \/repos\/{owner}\/{repo}\/git\/trees\/{sha}@
-- 
-- Gets the tree of a repository.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getTree
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  sha of the commit
  -> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
getTree :: Owner
-> Repo
-> Sha
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
getTree (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/trees/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse 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 GetTree  

-- | /Optional Param/ "recursive" - show all directories and files
instance HasOptionalParam GetTree Recursive where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> Recursive -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (Recursive Bool
xs) =
    GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"recursive", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "page" - page number; the 'truncated' field in the response will be true if there are still more items after this page, false if the last page
instance HasOptionalParam GetTree Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> Page -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (Page Int
xs) =
    GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "per_page" - number of items per page
instance HasOptionalParam GetTree PerPage where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> PerPage -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (PerPage Int
xs) =
    GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"per_page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces GetTree MimeJSON


-- *** listActionTasks

-- | @GET \/repos\/{owner}\/{repo}\/actions\/tasks@
-- 
-- List a repository's action tasks
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
listActionTasks
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
listActionTasks :: Owner
-> Repo
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
listActionTasks (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/tasks"]
    GiteaRequest
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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
  ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     ListActionTasks MimeNoContent ActionTaskResponse 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 ListActionTasks  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam ListActionTasks Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest ListActionTasks contentType res accept
-> Page -> GiteaRequest ListActionTasks contentType res accept
applyOptionalParam GiteaRequest ListActionTasks contentType res accept
req (Page Int
xs) =
    GiteaRequest ListActionTasks contentType res accept
req GiteaRequest ListActionTasks contentType res accept
-> [QueryItem]
-> GiteaRequest ListActionTasks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results, default maximum page size is 50
instance HasOptionalParam ListActionTasks Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest ListActionTasks contentType res accept
-> Limit -> GiteaRequest ListActionTasks contentType res accept
applyOptionalParam GiteaRequest ListActionTasks contentType res accept
req (Limit Int
xs) =
    GiteaRequest ListActionTasks contentType res accept
req GiteaRequest ListActionTasks contentType res accept
-> [QueryItem]
-> GiteaRequest ListActionTasks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces ListActionTasks MimeJSON


-- *** listForks

-- | @GET \/repos\/{owner}\/{repo}\/forks@
-- 
-- List a repository's forks
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
listForks
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
listForks :: Owner
-> Repo
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
listForks (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/forks"]
    GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest ListForks MimeNoContent [Repository] 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 ListForks  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam ListForks Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest ListForks contentType res accept
-> Page -> GiteaRequest ListForks contentType res accept
applyOptionalParam GiteaRequest ListForks contentType res accept
req (Page Int
xs) =
    GiteaRequest ListForks contentType res accept
req GiteaRequest ListForks contentType res accept
-> [QueryItem] -> GiteaRequest ListForks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam ListForks Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest ListForks contentType res accept
-> Limit -> GiteaRequest ListForks contentType res accept
applyOptionalParam GiteaRequest ListForks contentType res accept
req (Limit Int
xs) =
    GiteaRequest ListForks contentType res accept
req GiteaRequest ListForks contentType res accept
-> [QueryItem] -> GiteaRequest ListForks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces ListForks MimeJSON


-- *** rejectRepoTransfer

-- | @POST \/repos\/{owner}\/{repo}\/transfer\/reject@
-- 
-- Reject a repo transfer
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
rejectRepoTransfer
  :: Owner -- ^ "owner" -  owner of the repo to transfer
  -> Repo -- ^ "repo" -  name of the repo to transfer
  -> GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
rejectRepoTransfer :: Owner
-> Repo
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository MimeJSON
rejectRepoTransfer (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer/reject"]
    GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RejectRepoTransfer MimeNoContent Repository 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 RejectRepoTransfer  
-- | @application/json@
instance Produces RejectRepoTransfer MimeJSON


-- *** repoAddCollaborator

-- | @PUT \/repos\/{owner}\/{repo}\/collaborators\/{collaborator}@
-- 
-- Add or Update a collaborator to a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoAddCollaborator
  :: (Consumes RepoAddCollaborator contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Collaborator -- ^ "collaborator" -  username of the collaborator to add
  -> GiteaRequest RepoAddCollaborator contentType NoContent MimeNoContent
repoAddCollaborator :: forall contentType.
Consumes RepoAddCollaborator contentType =>
ContentType contentType
-> Owner
-> Repo
-> Collaborator
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
repoAddCollaborator ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
    GiteaRequest
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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
  RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoAddCollaborator contentType NoContent MimeNoContent
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 RepoAddCollaborator 
instance HasBodyParam RepoAddCollaborator AddCollaboratorOption 

-- | @application/json@
instance Consumes RepoAddCollaborator MimeJSON
-- | @text/plain@
instance Consumes RepoAddCollaborator MimePlainText

instance Produces RepoAddCollaborator MimeNoContent


-- *** repoAddPushMirror

-- | @POST \/repos\/{owner}\/{repo}\/push_mirrors@
-- 
-- add a push mirror to the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoAddPushMirror
  :: (Consumes RepoAddPushMirror MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
repoAddPushMirror :: Consumes RepoAddPushMirror MimeJSON =>
Owner
-> Repo
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
repoAddPushMirror (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors"]
    GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror 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 RepoAddPushMirror 
instance HasBodyParam RepoAddPushMirror CreatePushMirrorOption 

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

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


-- *** repoAddTeam

-- | @PUT \/repos\/{owner}\/{repo}\/teams\/{team}@
-- 
-- Add a team to a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoAddTeam
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Team2 -- ^ "team" -  team name
  -> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
repoAddTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
repoAddTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
  Method
-> [ByteString]
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
    GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
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 RepoAddTeam  
instance Produces RepoAddTeam MimeNoContent


-- *** repoAddTopic

-- | @PUT \/repos\/{owner}\/{repo}\/topics\/{topic}@
-- 
-- Add a topic to a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoAddTopic
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> TopicText -- ^ "topic" -  name of the topic to add
  -> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
repoAddTopic :: Owner
-> Repo
-> TopicText
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
repoAddTopic (Owner Text
owner) (Repo Text
repo) (TopicText Text
topic) =
  Method
-> [ByteString]
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
topic]
    GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
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 RepoAddTopic  
instance Produces RepoAddTopic MimeNoContent


-- *** repoApplyDiffPatch

-- | @POST \/repos\/{owner}\/{repo}\/diffpatch@
-- 
-- Apply diff patch to repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoApplyDiffPatch
  :: (Consumes RepoApplyDiffPatch MimeJSON, MimeRender MimeJSON UpdateFileOptions)
  => UpdateFileOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
repoApplyDiffPatch :: (Consumes RepoApplyDiffPatch MimeJSON,
 MimeRender MimeJSON UpdateFileOptions) =>
UpdateFileOptions
-> Owner
-> Repo
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
repoApplyDiffPatch UpdateFileOptions
body (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/diffpatch"]
    GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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 RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse 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)
    GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> UpdateFileOptions
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
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 RepoApplyDiffPatch contentType,
 MimeRender contentType UpdateFileOptions) =>
GiteaRequest RepoApplyDiffPatch contentType res accept
-> UpdateFileOptions
-> GiteaRequest RepoApplyDiffPatch contentType res accept
`setBodyParam` UpdateFileOptions
body

data RepoApplyDiffPatch 
instance HasBodyParam RepoApplyDiffPatch UpdateFileOptions 

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

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


-- *** repoCancelScheduledAutoMerge

-- | @DELETE \/repos\/{owner}\/{repo}\/pulls\/{index}\/merge@
-- 
-- Cancel the scheduled auto merge for the given pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCancelScheduledAutoMerge
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to merge
  -> GiteaRequest RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
repoCancelScheduledAutoMerge :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
repoCancelScheduledAutoMerge (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
    GiteaRequest
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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
  RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
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 RepoCancelScheduledAutoMerge  
instance Produces RepoCancelScheduledAutoMerge MimeNoContent


-- *** repoChangeFiles

-- | @POST \/repos\/{owner}\/{repo}\/contents@
-- 
-- Modify multiple files in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoChangeFiles
  :: (Consumes RepoChangeFiles MimeJSON, MimeRender MimeJSON ChangeFilesOptions)
  => ChangeFilesOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
repoChangeFiles :: (Consumes RepoChangeFiles MimeJSON,
 MimeRender MimeJSON ChangeFilesOptions) =>
ChangeFilesOptions
-> Owner
-> Repo
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
repoChangeFiles ChangeFilesOptions
body (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents"]
    GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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 RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse 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)
    GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> ChangeFilesOptions
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
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 RepoChangeFiles contentType,
 MimeRender contentType ChangeFilesOptions) =>
GiteaRequest RepoChangeFiles contentType res accept
-> ChangeFilesOptions
-> GiteaRequest RepoChangeFiles contentType res accept
`setBodyParam` ChangeFilesOptions
body

data RepoChangeFiles 
instance HasBodyParam RepoChangeFiles ChangeFilesOptions 

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

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


-- *** repoCheckCollaborator

-- | @GET \/repos\/{owner}\/{repo}\/collaborators\/{collaborator}@
-- 
-- Check if a user is a collaborator of a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCheckCollaborator
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Collaborator -- ^ "collaborator" -  username of the collaborator
  -> GiteaRequest RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
repoCheckCollaborator :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
repoCheckCollaborator (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
    GiteaRequest
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
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 RepoCheckCollaborator  
instance Produces RepoCheckCollaborator MimeNoContent


-- *** repoCheckTeam

-- | @GET \/repos\/{owner}\/{repo}\/teams\/{team}@
-- 
-- Check if a team is assigned to a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCheckTeam
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Team2 -- ^ "team" -  team name
  -> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
repoCheckTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
repoCheckTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
  Method
-> [ByteString]
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
    GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team 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 RepoCheckTeam  
-- | @application/json@
instance Produces RepoCheckTeam MimeJSON


-- *** repoCompareDiff

-- | @GET \/repos\/{owner}\/{repo}\/compare\/{basehead}@
-- 
-- Get commit comparison information
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCompareDiff
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Basehead -- ^ "basehead" -  compare two branches or commits
  -> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
repoCompareDiff :: Owner
-> Repo
-> Basehead
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
repoCompareDiff (Owner Text
owner) (Repo Text
repo) (Basehead Text
basehead) =
  Method
-> [ByteString]
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/compare/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
basehead]
    GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare 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 RepoCompareDiff  
-- | @application/json@
instance Produces RepoCompareDiff MimeJSON


-- *** repoCreateBranch

-- | @POST \/repos\/{owner}\/{repo}\/branches@
-- 
-- Create a branch
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateBranch
  :: (Consumes RepoCreateBranch MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
repoCreateBranch :: Consumes RepoCreateBranch MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
repoCreateBranch (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches"]
    GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch 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 RepoCreateBranch 
instance HasBodyParam RepoCreateBranch CreateBranchRepoOption 

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

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


-- *** repoCreateBranchProtection

-- | @POST \/repos\/{owner}\/{repo}\/branch_protections@
-- 
-- Create a branch protections for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateBranchProtection
  :: (Consumes RepoCreateBranchProtection MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
repoCreateBranchProtection :: Consumes RepoCreateBranchProtection MimeJSON =>
Owner
-> Repo
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
repoCreateBranchProtection (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections"]
    GiteaRequest
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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
  RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCreateBranchProtection MimeJSON BranchProtection 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 RepoCreateBranchProtection 
instance HasBodyParam RepoCreateBranchProtection CreateBranchProtectionOption 

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

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


-- *** repoCreateFile

-- | @POST \/repos\/{owner}\/{repo}\/contents\/{filepath}@
-- 
-- Create a file in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateFile
  :: (Consumes RepoCreateFile MimeJSON, MimeRender MimeJSON CreateFileOptions)
  => CreateFileOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the file to create
  -> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
repoCreateFile :: (Consumes RepoCreateFile MimeJSON,
 MimeRender MimeJSON CreateFileOptions) =>
CreateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
repoCreateFile CreateFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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 RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse 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)
    GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> CreateFileOptions
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
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 RepoCreateFile contentType,
 MimeRender contentType CreateFileOptions) =>
GiteaRequest RepoCreateFile contentType res accept
-> CreateFileOptions
-> GiteaRequest RepoCreateFile contentType res accept
`setBodyParam` CreateFileOptions
body

data RepoCreateFile 
instance HasBodyParam RepoCreateFile CreateFileOptions 

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

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


-- *** repoCreateHook

-- | @POST \/repos\/{owner}\/{repo}\/hooks@
-- 
-- Create a hook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateHook
  :: (Consumes RepoCreateHook MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
repoCreateHook :: Consumes RepoCreateHook MimeJSON =>
Owner -> Repo -> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
repoCreateHook (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks"]
    GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateHook MimeJSON Hook 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 RepoCreateHook 
instance HasBodyParam RepoCreateHook CreateHookOption 

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

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


-- *** repoCreateKey

-- | @POST \/repos\/{owner}\/{repo}\/keys@
-- 
-- Add a key to a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateKey
  :: (Consumes RepoCreateKey MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
repoCreateKey :: Consumes RepoCreateKey MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
repoCreateKey (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys"]
    GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey 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 RepoCreateKey 
instance HasBodyParam RepoCreateKey CreateKeyOption 

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

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


-- *** repoCreatePullRequest

-- | @POST \/repos\/{owner}\/{repo}\/pulls@
-- 
-- Create a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreatePullRequest
  :: (Consumes RepoCreatePullRequest MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
repoCreatePullRequest :: Consumes RepoCreatePullRequest MimeJSON =>
Owner
-> Repo
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
repoCreatePullRequest (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls"]
    GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest 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 RepoCreatePullRequest 
instance HasBodyParam RepoCreatePullRequest CreatePullRequestOption 

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

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


-- *** repoCreatePullReview

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews@
-- 
-- Create a review to an pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreatePullReview
  :: (Consumes RepoCreatePullReview contentType, MimeRender contentType CreatePullReviewOptions)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> CreatePullReviewOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
repoCreatePullReview :: forall contentType.
(Consumes RepoCreatePullReview contentType,
 MimeRender contentType CreatePullReviewOptions) =>
ContentType contentType
-> CreatePullReviewOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
     RepoCreatePullReview contentType PullReview MimeJSON
repoCreatePullReview ContentType contentType
_ CreatePullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCreatePullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews"]
    GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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 RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCreatePullReview contentType PullReview 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)
    GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> CreatePullReviewOptions
-> GiteaRequest
     RepoCreatePullReview contentType PullReview MimeJSON
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 RepoCreatePullReview contentType,
 MimeRender contentType CreatePullReviewOptions) =>
GiteaRequest RepoCreatePullReview contentType res accept
-> CreatePullReviewOptions
-> GiteaRequest RepoCreatePullReview contentType res accept
`setBodyParam` CreatePullReviewOptions
body

data RepoCreatePullReview 
instance HasBodyParam RepoCreatePullReview CreatePullReviewOptions 

-- | @application/json@
instance Consumes RepoCreatePullReview MimeJSON
-- | @text/plain@
instance Consumes RepoCreatePullReview MimePlainText

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


-- *** repoCreatePullReviewRequests

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/requested_reviewers@
-- 
-- create review requests for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreatePullReviewRequests
  :: (Consumes RepoCreatePullReviewRequests contentType, MimeRender contentType PullReviewRequestOptions)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> PullReviewRequestOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> GiteaRequest RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
repoCreatePullReviewRequests :: forall contentType.
(Consumes RepoCreatePullReviewRequests contentType,
 MimeRender contentType PullReviewRequestOptions) =>
ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
repoCreatePullReviewRequests ContentType contentType
_ PullReviewRequestOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/requested_reviewers"]
    GiteaRequest
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] 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)
    GiteaRequest
  RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> PullReviewRequestOptions
-> GiteaRequest
     RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
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 RepoCreatePullReviewRequests contentType,
 MimeRender contentType PullReviewRequestOptions) =>
GiteaRequest RepoCreatePullReviewRequests contentType res accept
-> PullReviewRequestOptions
-> GiteaRequest RepoCreatePullReviewRequests contentType res accept
`setBodyParam` PullReviewRequestOptions
body

data RepoCreatePullReviewRequests 
instance HasBodyParam RepoCreatePullReviewRequests PullReviewRequestOptions 

-- | @application/json@
instance Consumes RepoCreatePullReviewRequests MimeJSON
-- | @text/plain@
instance Consumes RepoCreatePullReviewRequests MimePlainText

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


-- *** repoCreateRelease

-- | @POST \/repos\/{owner}\/{repo}\/releases@
-- 
-- Create a release
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateRelease
  :: (Consumes RepoCreateRelease MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
repoCreateRelease :: Consumes RepoCreateRelease MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
repoCreateRelease (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases"]
    GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateRelease MimeJSON Release 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 RepoCreateRelease 
instance HasBodyParam RepoCreateRelease CreateReleaseOption 

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

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


-- *** repoCreateReleaseAttachment

-- | @POST \/repos\/{owner}\/{repo}\/releases\/{id}\/assets@
-- 
-- Create a release attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateReleaseAttachment
  :: (Consumes RepoCreateReleaseAttachment contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release
  -> GiteaRequest RepoCreateReleaseAttachment contentType Attachment MimeJSON
repoCreateReleaseAttachment :: forall contentType.
Consumes RepoCreateReleaseAttachment contentType =>
ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment MimeJSON
repoCreateReleaseAttachment ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets"]
    GiteaRequest
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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
  RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCreateReleaseAttachment contentType Attachment 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 RepoCreateReleaseAttachment  

-- | /Optional Param/ "attachment" - attachment to upload
instance HasOptionalParam RepoCreateReleaseAttachment Attachment2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Attachment2
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
applyOptionalParam GiteaRequest RepoCreateReleaseAttachment contentType res accept
req (Attachment2 FilePath
xs) =
    GiteaRequest RepoCreateReleaseAttachment contentType res accept
req GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Part
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> Part -> GiteaRequest req contentType res accept
`_addMultiFormPart` Text -> FilePath -> Part
NH.partFileSource Text
"attachment" FilePath
xs

-- | /Optional Param/ "name" - name of the attachment
instance HasOptionalParam RepoCreateReleaseAttachment Name where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Name
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
applyOptionalParam GiteaRequest RepoCreateReleaseAttachment contentType res accept
req (Name Text
xs) =
    GiteaRequest RepoCreateReleaseAttachment contentType res accept
req GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> [QueryItem]
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"name", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @application/octet-stream@
instance Consumes RepoCreateReleaseAttachment MimeOctetStream
-- | @multipart/form-data@
instance Consumes RepoCreateReleaseAttachment MimeMultipartFormData

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


-- *** repoCreateStatus

-- | @POST \/repos\/{owner}\/{repo}\/statuses\/{sha}@
-- 
-- Create a commit status
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateStatus
  :: (Consumes RepoCreateStatus contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  sha of the commit
  -> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
repoCreateStatus :: forall contentType.
Consumes RepoCreateStatus contentType =>
ContentType contentType
-> Owner
-> Repo
-> Sha
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
repoCreateStatus ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/statuses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus 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 RepoCreateStatus 
instance HasBodyParam RepoCreateStatus CreateStatusOption 

-- | @application/json@
instance Consumes RepoCreateStatus MimeJSON
-- | @text/plain@
instance Consumes RepoCreateStatus MimePlainText

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


-- *** repoCreateTag

-- | @POST \/repos\/{owner}\/{repo}\/tags@
-- 
-- Create a new git tag in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateTag
  :: (Consumes RepoCreateTag contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateTag contentType Tag MimeJSON
repoCreateTag :: forall contentType.
Consumes RepoCreateTag contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
repoCreateTag ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags"]
    GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateTag contentType Tag 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 RepoCreateTag 
instance HasBodyParam RepoCreateTag CreateTagOption 

-- | @application/json@
instance Consumes RepoCreateTag MimeJSON
-- | @text/plain@
instance Consumes RepoCreateTag MimePlainText

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


-- *** repoCreateTagProtection

-- | @POST \/repos\/{owner}\/{repo}\/tag_protections@
-- 
-- Create a tag protections for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateTagProtection
  :: (Consumes RepoCreateTagProtection MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateTagProtection MimeJSON TagProtection MimeJSON
repoCreateTagProtection :: Consumes RepoCreateTagProtection MimeJSON =>
Owner
-> Repo
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection MimeJSON
repoCreateTagProtection (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections"]
    GiteaRequest
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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
  RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoCreateTagProtection MimeJSON TagProtection 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 RepoCreateTagProtection 
instance HasBodyParam RepoCreateTagProtection CreateTagProtectionOption 

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

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


-- *** repoCreateWikiPage

-- | @POST \/repos\/{owner}\/{repo}\/wiki\/new@
-- 
-- Create a wiki page
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoCreateWikiPage
  :: (Consumes RepoCreateWikiPage MimeJSON)
  => Accept accept -- ^ request accept ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
repoCreateWikiPage :: forall accept.
Consumes RepoCreateWikiPage MimeJSON =>
Accept accept
-> Owner
-> Repo
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
repoCreateWikiPage  Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/new"]
    GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
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 RepoCreateWikiPage 
instance HasBodyParam RepoCreateWikiPage CreateWikiPageOptions 

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

-- | @text/html@
instance Produces RepoCreateWikiPage MimeTextHtml
-- | @application/json@
instance Produces RepoCreateWikiPage MimeJSON


-- *** repoDelete

-- | @DELETE \/repos\/{owner}\/{repo}@
-- 
-- Delete a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDelete
  :: Owner -- ^ "owner" -  owner of the repo to delete
  -> Repo -- ^ "repo" -  name of the repo to delete
  -> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
repoDelete :: Owner
-> Repo
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
repoDelete (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
    GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
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 RepoDelete  
instance Produces RepoDelete MimeNoContent


-- *** repoDeleteAvatar

-- | @DELETE \/repos\/{owner}\/{repo}\/avatar@
-- 
-- Delete avatar
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteAvatar
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
repoDeleteAvatar :: Owner
-> Repo
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
repoDeleteAvatar (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/avatar"]
    GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
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 RepoDeleteAvatar  
instance Produces RepoDeleteAvatar MimeNoContent


-- *** repoDeleteBranch

-- | @DELETE \/repos\/{owner}\/{repo}\/branches\/{branch}@
-- 
-- Delete a specific branch from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteBranch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Branch2 -- ^ "branch" -  branch to delete
  -> GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
repoDeleteBranch :: Owner
-> Repo
-> Branch2
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
repoDeleteBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
    GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteBranch MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranch  
instance Produces RepoDeleteBranch MimeNoContent


-- *** repoDeleteBranchProtection

-- | @DELETE \/repos\/{owner}\/{repo}\/branch_protections\/{name}@
-- 
-- Delete a specific branch protection for the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteBranchProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Name -- ^ "name" -  name of protected branch
  -> GiteaRequest RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
repoDeleteBranchProtection :: Owner
-> Repo
-> Name
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
repoDeleteBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
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 RepoDeleteBranchProtection  
instance Produces RepoDeleteBranchProtection MimeNoContent


-- *** repoDeleteCollaborator

-- | @DELETE \/repos\/{owner}\/{repo}\/collaborators\/{collaborator}@
-- 
-- Delete a collaborator from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteCollaborator
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Collaborator -- ^ "collaborator" -  username of the collaborator to delete
  -> GiteaRequest RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
repoDeleteCollaborator :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
repoDeleteCollaborator (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
    GiteaRequest
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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
  RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
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 RepoDeleteCollaborator  
instance Produces RepoDeleteCollaborator MimeNoContent


-- *** repoDeleteFile

-- | @DELETE \/repos\/{owner}\/{repo}\/contents\/{filepath}@
-- 
-- Delete a file in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteFile
  :: (Consumes RepoDeleteFile MimeJSON, MimeRender MimeJSON DeleteFileOptions)
  => DeleteFileOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the file to delete
  -> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
repoDeleteFile :: (Consumes RepoDeleteFile MimeJSON,
 MimeRender MimeJSON DeleteFileOptions) =>
DeleteFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
repoDeleteFile DeleteFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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 RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse 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)
    GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> DeleteFileOptions
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
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 RepoDeleteFile contentType,
 MimeRender contentType DeleteFileOptions) =>
GiteaRequest RepoDeleteFile contentType res accept
-> DeleteFileOptions
-> GiteaRequest RepoDeleteFile contentType res accept
`setBodyParam` DeleteFileOptions
body

data RepoDeleteFile 
instance HasBodyParam RepoDeleteFile DeleteFileOptions 

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

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


-- *** repoDeleteGitHook

-- | @DELETE \/repos\/{owner}\/{repo}\/hooks\/git\/{id}@
-- 
-- Delete a Git hook in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteGitHook
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  id of the hook to get
  -> GiteaRequest RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
repoDeleteGitHook :: Owner
-> Repo
-> IdText
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
repoDeleteGitHook (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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
  RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteGitHook  
instance Produces RepoDeleteGitHook MimeNoContent


-- *** repoDeleteHook

-- | @DELETE \/repos\/{owner}\/{repo}\/hooks\/{id}@
-- 
-- Delete a hook in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteHook
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the hook to delete
  -> GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
repoDeleteHook :: Owner
-> Repo
-> Id
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
repoDeleteHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteHook MimeNoContent NoContent MimeNoContent
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 RepoDeleteHook  
instance Produces RepoDeleteHook MimeNoContent


-- *** repoDeleteKey

-- | @DELETE \/repos\/{owner}\/{repo}\/keys\/{id}@
-- 
-- Delete a key from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteKey
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the key to delete
  -> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
repoDeleteKey :: Owner
-> Repo
-> Id
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
repoDeleteKey (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
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 RepoDeleteKey  
instance Produces RepoDeleteKey MimeNoContent


-- *** repoDeletePullReview

-- | @DELETE \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}@
-- 
-- Delete a specific review from a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeletePullReview
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoDeletePullReview MimeNoContent NoContent MimeNoContent
repoDeletePullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
repoDeletePullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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
  RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeletePullReview MimeNoContent NoContent MimeNoContent
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 RepoDeletePullReview  
instance Produces RepoDeletePullReview MimeNoContent


-- *** repoDeletePullReviewRequests

-- | @DELETE \/repos\/{owner}\/{repo}\/pulls\/{index}\/requested_reviewers@
-- 
-- cancel review requests for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeletePullReviewRequests
  :: (Consumes RepoDeletePullReviewRequests contentType, MimeRender contentType PullReviewRequestOptions)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> PullReviewRequestOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> GiteaRequest RepoDeletePullReviewRequests contentType NoContent MimeNoContent
repoDeletePullReviewRequests :: forall contentType.
(Consumes RepoDeletePullReviewRequests contentType,
 MimeRender contentType PullReviewRequestOptions) =>
ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
repoDeletePullReviewRequests ContentType contentType
_ PullReviewRequestOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/requested_reviewers"]
    GiteaRequest
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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
  RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> PullReviewRequestOptions
-> GiteaRequest
     RepoDeletePullReviewRequests contentType NoContent MimeNoContent
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 RepoDeletePullReviewRequests contentType,
 MimeRender contentType PullReviewRequestOptions) =>
GiteaRequest RepoDeletePullReviewRequests contentType res accept
-> PullReviewRequestOptions
-> GiteaRequest RepoDeletePullReviewRequests contentType res accept
`setBodyParam` PullReviewRequestOptions
body

data RepoDeletePullReviewRequests 
instance HasBodyParam RepoDeletePullReviewRequests PullReviewRequestOptions 

-- | @application/json@
instance Consumes RepoDeletePullReviewRequests MimeJSON
-- | @text/plain@
instance Consumes RepoDeletePullReviewRequests MimePlainText

instance Produces RepoDeletePullReviewRequests MimeNoContent


-- *** repoDeletePushMirror

-- | @DELETE \/repos\/{owner}\/{repo}\/push_mirrors\/{name}@
-- 
-- deletes a push mirror from a repository by remoteName
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeletePushMirror
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Name -- ^ "name" -  remote name of the pushMirror
  -> GiteaRequest RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
repoDeletePushMirror :: Owner
-> Repo
-> Name
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
repoDeletePushMirror (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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
  RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
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 RepoDeletePushMirror  
instance Produces RepoDeletePushMirror MimeNoContent


-- *** repoDeleteRelease

-- | @DELETE \/repos\/{owner}\/{repo}\/releases\/{id}@
-- 
-- Delete a release
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteRelease
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release to delete
  -> GiteaRequest RepoDeleteRelease MimeNoContent NoContent MimeNoContent
repoDeleteRelease :: Owner
-> Repo
-> Id
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
repoDeleteRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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
  RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteRelease MimeNoContent NoContent MimeNoContent
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 RepoDeleteRelease  
instance Produces RepoDeleteRelease MimeNoContent


-- *** repoDeleteReleaseAttachment

-- | @DELETE \/repos\/{owner}\/{repo}\/releases\/{id}\/assets\/{attachment_id}@
-- 
-- Delete a release attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteReleaseAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to delete
  -> GiteaRequest RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
repoDeleteReleaseAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
repoDeleteReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
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 RepoDeleteReleaseAttachment  
instance Produces RepoDeleteReleaseAttachment MimeNoContent


-- *** repoDeleteReleaseByTag

-- | @DELETE \/repos\/{owner}\/{repo}\/releases\/tags\/{tag}@
-- 
-- Delete a release by tag name
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteReleaseByTag
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Tag2 -- ^ "tag" -  tag name of the release to delete
  -> GiteaRequest RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
repoDeleteReleaseByTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
repoDeleteReleaseByTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
    GiteaRequest
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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
  RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteReleaseByTag  
instance Produces RepoDeleteReleaseByTag MimeNoContent


-- *** repoDeleteTag

-- | @DELETE \/repos\/{owner}\/{repo}\/tags\/{tag}@
-- 
-- Delete a repository's tag by name
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteTag
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Tag2 -- ^ "tag" -  name of tag to delete
  -> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
repoDeleteTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
repoDeleteTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
  Method
-> [ByteString]
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
    GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
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 RepoDeleteTag  
instance Produces RepoDeleteTag MimeNoContent


-- *** repoDeleteTagProtection

-- | @DELETE \/repos\/{owner}\/{repo}\/tag_protections\/{id}@
-- 
-- Delete a specific tag protection for the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteTagProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdInt -- ^ "id" -  id of protected tag
  -> GiteaRequest RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
repoDeleteTagProtection :: Owner
-> Repo
-> IdInt
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
repoDeleteTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    GiteaRequest
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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
  RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
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 RepoDeleteTagProtection  
instance Produces RepoDeleteTagProtection MimeNoContent


-- *** repoDeleteTeam

-- | @DELETE \/repos\/{owner}\/{repo}\/teams\/{team}@
-- 
-- Delete a team from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteTeam
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Team2 -- ^ "team" -  team name
  -> GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
repoDeleteTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
repoDeleteTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
    GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteTeam MimeNoContent NoContent MimeNoContent
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 RepoDeleteTeam  
instance Produces RepoDeleteTeam MimeNoContent


-- *** repoDeleteTopic

-- | @DELETE \/repos\/{owner}\/{repo}\/topics\/{topic}@
-- 
-- Delete a topic from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteTopic
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> TopicText -- ^ "topic" -  name of the topic to delete
  -> GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
repoDeleteTopic :: Owner
-> Repo
-> TopicText
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
repoDeleteTopic (Owner Text
owner) (Repo Text
repo) (TopicText Text
topic) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
topic]
    GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteTopic MimeNoContent NoContent MimeNoContent
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 RepoDeleteTopic  
instance Produces RepoDeleteTopic MimeNoContent


-- *** repoDeleteWikiPage

-- | @DELETE \/repos\/{owner}\/{repo}\/wiki\/page\/{pageName}@
-- 
-- Delete a wiki page
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDeleteWikiPage
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> PageName -- ^ "pageName" -  name of the page
  -> GiteaRequest RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
repoDeleteWikiPage :: Owner
-> Repo
-> PageName
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
repoDeleteWikiPage (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
    GiteaRequest
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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
  RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
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 RepoDeleteWikiPage  
instance Produces RepoDeleteWikiPage MimeNoContent


-- *** repoDismissPullReview

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}\/dismissals@
-- 
-- Dismiss a review for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDismissPullReview
  :: (Consumes RepoDismissPullReview contentType, MimeRender contentType DismissPullReviewOptions)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> DismissPullReviewOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
repoDismissPullReview :: forall contentType.
(Consumes RepoDismissPullReview contentType,
 MimeRender contentType DismissPullReviewOptions) =>
ContentType contentType
-> DismissPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     RepoDismissPullReview contentType PullReview MimeJSON
repoDismissPullReview ContentType contentType
_ DismissPullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDismissPullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/dismissals"]
    GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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 RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDismissPullReview contentType PullReview 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)
    GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> DismissPullReviewOptions
-> GiteaRequest
     RepoDismissPullReview contentType PullReview MimeJSON
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 RepoDismissPullReview contentType,
 MimeRender contentType DismissPullReviewOptions) =>
GiteaRequest RepoDismissPullReview contentType res accept
-> DismissPullReviewOptions
-> GiteaRequest RepoDismissPullReview contentType res accept
`setBodyParam` DismissPullReviewOptions
body

data RepoDismissPullReview 
instance HasBodyParam RepoDismissPullReview DismissPullReviewOptions 

-- | @application/json@
instance Consumes RepoDismissPullReview MimeJSON
-- | @text/plain@
instance Consumes RepoDismissPullReview MimePlainText

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


-- *** repoDownloadCommitDiffOrPatch

-- | @GET \/repos\/{owner}\/{repo}\/git\/commits\/{sha}.{diffType}@
-- 
-- Get a commit's diff or patch
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDownloadCommitDiffOrPatch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  SHA of the commit to get
  -> DiffType -- ^ "diffType" -  whether the output is diff or patch
  -> GiteaRequest RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadCommitDiffOrPatch :: Owner
-> Repo
-> Sha
-> DiffType
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadCommitDiffOrPatch (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) (DiffType E'DiffType
diffType) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha,ByteString
".",E'DiffType -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath E'DiffType
diffType]
    GiteaRequest
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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
  RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDownloadCommitDiffOrPatch 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 RepoDownloadCommitDiffOrPatch  
-- | @text/plain@
instance Produces RepoDownloadCommitDiffOrPatch MimePlainText


-- *** repoDownloadPullDiffOrPatch

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}.{diffType}@
-- 
-- Get a pull request diff or patch
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoDownloadPullDiffOrPatch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to get
  -> DiffType -- ^ "diffType" -  whether the output is diff or patch
  -> GiteaRequest RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadPullDiffOrPatch :: Owner
-> Repo
-> Index
-> DiffType
-> GiteaRequest
     RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadPullDiffOrPatch (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (DiffType E'DiffType
diffType) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
".",E'DiffType -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath E'DiffType
diffType]
    GiteaRequest
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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
  RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoDownloadPullDiffOrPatch 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 RepoDownloadPullDiffOrPatch  

-- | /Optional Param/ "binary" - whether to include binary file changes. if true, the diff is applicable with `git apply`
instance HasOptionalParam RepoDownloadPullDiffOrPatch ParamBinary where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
-> ParamBinary
-> GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
applyOptionalParam GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
req (ParamBinary Bool
xs) =
    GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
req GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
-> [QueryItem]
-> GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"binary", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @text/plain@
instance Produces RepoDownloadPullDiffOrPatch MimePlainText


-- *** repoEdit

-- | @PATCH \/repos\/{owner}\/{repo}@
-- 
-- Edit a repository's properties. Only fields that are set will be changed.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEdit
  :: (Consumes RepoEdit contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo to edit
  -> Repo -- ^ "repo" -  name of the repo to edit
  -> GiteaRequest RepoEdit contentType Repository MimeJSON
repoEdit :: forall contentType.
Consumes RepoEdit contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoEdit contentType Repository MimeJSON
repoEdit ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
    GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEdit contentType Repository 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 RepoEdit 

-- | /Body Param/ "body" - Properties of a repo that you can edit
instance HasBodyParam RepoEdit EditRepoOption 

-- | @application/json@
instance Consumes RepoEdit MimeJSON
-- | @text/plain@
instance Consumes RepoEdit MimePlainText

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


-- *** repoEditBranchProtection

-- | @PATCH \/repos\/{owner}\/{repo}\/branch_protections\/{name}@
-- 
-- Edit a branch protections for a repository. Only fields that are set will be changed
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditBranchProtection
  :: (Consumes RepoEditBranchProtection MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Name -- ^ "name" -  name of protected branch
  -> GiteaRequest RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
repoEditBranchProtection :: Consumes RepoEditBranchProtection MimeJSON =>
Owner
-> Repo
-> Name
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
repoEditBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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
  RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoEditBranchProtection MimeJSON BranchProtection 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 RepoEditBranchProtection 
instance HasBodyParam RepoEditBranchProtection EditBranchProtectionOption 

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

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


-- *** repoEditGitHook

-- | @PATCH \/repos\/{owner}\/{repo}\/hooks\/git\/{id}@
-- 
-- Edit a Git hook in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditGitHook
  :: (Consumes RepoEditGitHook contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  id of the hook to get
  -> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
repoEditGitHook :: forall contentType.
Consumes RepoEditGitHook contentType =>
ContentType contentType
-> Owner
-> Repo
-> IdText
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
repoEditGitHook ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditGitHook contentType GitHook 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 RepoEditGitHook 
instance HasBodyParam RepoEditGitHook EditGitHookOption 

-- | @application/json@
instance Consumes RepoEditGitHook MimeJSON
-- | @text/plain@
instance Consumes RepoEditGitHook MimePlainText

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


-- *** repoEditHook

-- | @PATCH \/repos\/{owner}\/{repo}\/hooks\/{id}@
-- 
-- Edit a hook in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditHook
  :: (Consumes RepoEditHook contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  index of the hook
  -> GiteaRequest RepoEditHook contentType Hook MimeJSON
repoEditHook :: forall contentType.
Consumes RepoEditHook contentType =>
ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
repoEditHook ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditHook contentType Hook 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 RepoEditHook 
instance HasBodyParam RepoEditHook EditHookOption 

-- | @application/json@
instance Consumes RepoEditHook MimeJSON
-- | @text/plain@
instance Consumes RepoEditHook MimePlainText

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


-- *** repoEditPullRequest

-- | @PATCH \/repos\/{owner}\/{repo}\/pulls\/{index}@
-- 
-- Update a pull request. If using deadline only the date will be taken into account, and time of day ignored.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditPullRequest
  :: (Consumes RepoEditPullRequest MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to edit
  -> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
repoEditPullRequest :: Consumes RepoEditPullRequest MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
repoEditPullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
    GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest 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 RepoEditPullRequest 
instance HasBodyParam RepoEditPullRequest EditPullRequestOption 

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

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


-- *** repoEditRelease

-- | @PATCH \/repos\/{owner}\/{repo}\/releases\/{id}@
-- 
-- Update a release
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditRelease
  :: (Consumes RepoEditRelease MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release to edit
  -> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
repoEditRelease :: Consumes RepoEditRelease MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
repoEditRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditRelease MimeJSON Release 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 RepoEditRelease 
instance HasBodyParam RepoEditRelease EditReleaseOption 

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

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


-- *** repoEditReleaseAttachment

-- | @PATCH \/repos\/{owner}\/{repo}\/releases\/{id}\/assets\/{attachment_id}@
-- 
-- Edit a release attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditReleaseAttachment
  :: (Consumes RepoEditReleaseAttachment MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to edit
  -> GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
repoEditReleaseAttachment :: Consumes RepoEditReleaseAttachment MimeJSON =>
Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
repoEditReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoEditReleaseAttachment MimeJSON Attachment 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 RepoEditReleaseAttachment 
instance HasBodyParam RepoEditReleaseAttachment EditAttachmentOptions 

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

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


-- *** repoEditTagProtection

-- | @PATCH \/repos\/{owner}\/{repo}\/tag_protections\/{id}@
-- 
-- Edit a tag protections for a repository. Only fields that are set will be changed
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditTagProtection
  :: (Consumes RepoEditTagProtection MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdInt -- ^ "id" -  id of protected tag
  -> GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
repoEditTagProtection :: Consumes RepoEditTagProtection MimeJSON =>
Owner
-> Repo
-> IdInt
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection MimeJSON
repoEditTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoEditTagProtection MimeJSON TagProtection 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 RepoEditTagProtection 
instance HasBodyParam RepoEditTagProtection EditTagProtectionOption 

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

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


-- *** repoEditWikiPage

-- | @PATCH \/repos\/{owner}\/{repo}\/wiki\/page\/{pageName}@
-- 
-- Edit a wiki page
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoEditWikiPage
  :: (Consumes RepoEditWikiPage MimeJSON)
  => Accept accept -- ^ request accept ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> PageName -- ^ "pageName" -  name of the page
  -> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
repoEditWikiPage :: forall accept.
Consumes RepoEditWikiPage MimeJSON =>
Accept accept
-> Owner
-> Repo
-> PageName
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
repoEditWikiPage  Accept accept
_ (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
  Method
-> [ByteString]
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
    GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
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 RepoEditWikiPage 
instance HasBodyParam RepoEditWikiPage CreateWikiPageOptions 

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

-- | @text/html@
instance Produces RepoEditWikiPage MimeTextHtml
-- | @application/json@
instance Produces RepoEditWikiPage MimeJSON


-- *** repoGet

-- | @GET \/repos\/{owner}\/{repo}@
-- 
-- Get a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGet
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
repoGet :: Owner
-> Repo -> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
repoGet (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
    GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGet MimeNoContent Repository 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 RepoGet  
-- | @application/json@
instance Produces RepoGet MimeJSON


-- *** repoGetAllCommits

-- | @GET \/repos\/{owner}\/{repo}\/commits@
-- 
-- Get a list of all commits from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetAllCommits
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
repoGetAllCommits :: Owner
-> Repo
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
repoGetAllCommits (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits"]
    GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] 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 RepoGetAllCommits  

-- | /Optional Param/ "sha" - SHA or branch to start listing commits from (usually 'master')
instance HasOptionalParam RepoGetAllCommits Sha where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Sha -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Sha Text
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sha", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "path" - filepath of a file/dir
instance HasOptionalParam RepoGetAllCommits Path where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Path -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Path Text
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "stat" - include diff stats for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetAllCommits Stat where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Stat -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Stat Bool
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stat", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "verification" - include verification for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetAllCommits Verification where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Verification
-> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Verification Bool
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "files" - include a list of affected files for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetAllCommits Files where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Files -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Files Bool
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetAllCommits Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Page -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results (ignored if used with 'path')
instance HasOptionalParam RepoGetAllCommits Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Limit -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "not" - commits that match the given specifier will not be listed.
instance HasOptionalParam RepoGetAllCommits Not where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Not -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Not Text
xs) =
    GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"not", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces RepoGetAllCommits MimeJSON


-- *** repoGetArchive

-- | @GET \/repos\/{owner}\/{repo}\/archive\/{archive}@
-- 
-- Get an archive of a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetArchive
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Archive -- ^ "archive" -  the git reference for download with attached archive format (e.g. master.zip)
  -> GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
repoGetArchive :: Owner
-> Repo
-> Archive
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
repoGetArchive (Owner Text
owner) (Repo Text
repo) (Archive Text
archive) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/archive/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
archive]
    GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetArchive MimeNoContent NoContent MimeNoContent
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 RepoGetArchive  
instance Produces RepoGetArchive MimeNoContent


-- *** repoGetAssignees

-- | @GET \/repos\/{owner}\/{repo}\/assignees@
-- 
-- Return all users that have write access and can be assigned to issues
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetAssignees
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
repoGetAssignees :: Owner
-> Repo
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
repoGetAssignees (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/assignees"]
    GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] 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 RepoGetAssignees  
-- | @application/json@
instance Produces RepoGetAssignees MimeJSON


-- *** repoGetBranch

-- | @GET \/repos\/{owner}\/{repo}\/branches\/{branch}@
-- 
-- Retrieve a specific branch from a repository, including its effective branch protection
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetBranch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Branch2 -- ^ "branch" -  branch to get
  -> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
repoGetBranch :: Owner
-> Repo
-> Branch2
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
repoGetBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
    GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch 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 RepoGetBranch  
-- | @application/json@
instance Produces RepoGetBranch MimeJSON


-- *** repoGetBranchProtection

-- | @GET \/repos\/{owner}\/{repo}\/branch_protections\/{name}@
-- 
-- Get a specific branch protection for the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetBranchProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Name -- ^ "name" -  name of protected branch
  -> GiteaRequest RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
repoGetBranchProtection :: Owner
-> Repo
-> Name
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
repoGetBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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
  RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetBranchProtection MimeNoContent BranchProtection 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 RepoGetBranchProtection  
-- | @application/json@
instance Produces RepoGetBranchProtection MimeJSON


-- *** repoGetByID

-- | @GET \/repositories\/{id}@
-- 
-- Get a repository by id
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetByID
  :: Id -- ^ "id" -  id of the repo to get
  -> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
repoGetByID :: Id -> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
repoGetByID (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repositories/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetByID MimeNoContent Repository 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 RepoGetByID  
-- | @application/json@
instance Produces RepoGetByID MimeJSON


-- *** repoGetCombinedStatusByRef

-- | @GET \/repos\/{owner}\/{repo}\/commits\/{ref}\/status@
-- 
-- Get a commit's combined status, by branch/tag/commit reference
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetCombinedStatusByRef
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Ref -- ^ "ref" -  name of branch/tag/commit
  -> GiteaRequest RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
repoGetCombinedStatusByRef :: Owner
-> Repo
-> Ref
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
repoGetCombinedStatusByRef (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref,ByteString
"/status"]
    GiteaRequest
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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
  RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetCombinedStatusByRef MimeNoContent CombinedStatus 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 RepoGetCombinedStatusByRef  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetCombinedStatusByRef Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> Page
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
applyOptionalParam GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoGetCombinedStatusByRef Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> Limit
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
applyOptionalParam GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoGetCombinedStatusByRef MimeJSON


-- *** repoGetCommitPullRequest

-- | @GET \/repos\/{owner}\/{repo}\/commits\/{sha}\/pull@
-- 
-- Get the merged pull request of the commit
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetCommitPullRequest
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  SHA of the commit to get
  -> GiteaRequest RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
repoGetCommitPullRequest :: Owner
-> Repo
-> Sha
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
repoGetCommitPullRequest (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha,ByteString
"/pull"]
    GiteaRequest
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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
  RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetCommitPullRequest MimeNoContent PullRequest 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 RepoGetCommitPullRequest  
-- | @application/json@
instance Produces RepoGetCommitPullRequest MimeJSON


-- *** repoGetContents

-- | @GET \/repos\/{owner}\/{repo}\/contents\/{filepath}@
-- 
-- Gets the metadata and contents (if a file) of an entry in a repository, or a list of entries if a dir
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetContents
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the dir, file, symlink or submodule in the repo
  -> GiteaRequest RepoGetContents MimeNoContent ContentsResponse MimeJSON
repoGetContents :: Owner
-> Repo
-> Filepath
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse MimeJSON
repoGetContents (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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
  RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetContents MimeNoContent ContentsResponse 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 RepoGetContents  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag. Default the repository’s default branch (usually master)
instance HasOptionalParam RepoGetContents Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetContents contentType res accept
-> Ref -> GiteaRequest RepoGetContents contentType res accept
applyOptionalParam GiteaRequest RepoGetContents contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoGetContents contentType res accept
req GiteaRequest RepoGetContents contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetContents contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces RepoGetContents MimeJSON


-- *** repoGetContentsList

-- | @GET \/repos\/{owner}\/{repo}\/contents@
-- 
-- Gets the metadata of all the entries of the root dir
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetContentsList
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
repoGetContentsList :: Owner
-> Repo
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
repoGetContentsList (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents"]
    GiteaRequest
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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
  RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetContentsList MimeNoContent [ContentsResponse] 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 RepoGetContentsList  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag. Default the repository’s default branch (usually master)
instance HasOptionalParam RepoGetContentsList Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetContentsList contentType res accept
-> Ref -> GiteaRequest RepoGetContentsList contentType res accept
applyOptionalParam GiteaRequest RepoGetContentsList contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoGetContentsList contentType res accept
req GiteaRequest RepoGetContentsList contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetContentsList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces RepoGetContentsList MimeJSON


-- *** repoGetEditorConfig

-- | @GET \/repos\/{owner}\/{repo}\/editorconfig\/{filepath}@
-- 
-- Get the EditorConfig definitions of a file in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetEditorConfig
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  filepath of file to get
  -> GiteaRequest RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
repoGetEditorConfig :: Owner
-> Repo
-> Filepath
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
repoGetEditorConfig (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/editorconfig/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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
  RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
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 RepoGetEditorConfig  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag. Default the repository’s default branch (usually master)
instance HasOptionalParam RepoGetEditorConfig Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetEditorConfig contentType res accept
-> Ref -> GiteaRequest RepoGetEditorConfig contentType res accept
applyOptionalParam GiteaRequest RepoGetEditorConfig contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoGetEditorConfig contentType res accept
req GiteaRequest RepoGetEditorConfig contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetEditorConfig contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetEditorConfig MimeNoContent


-- *** repoGetGitHook

-- | @GET \/repos\/{owner}\/{repo}\/hooks\/git\/{id}@
-- 
-- Get a Git hook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetGitHook
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  id of the hook to get
  -> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
repoGetGitHook :: Owner
-> Repo
-> IdText
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
repoGetGitHook (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook 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 RepoGetGitHook  
-- | @application/json@
instance Produces RepoGetGitHook MimeJSON


-- *** repoGetHook

-- | @GET \/repos\/{owner}\/{repo}\/hooks\/{id}@
-- 
-- Get a hook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetHook
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the hook to get
  -> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
repoGetHook :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
repoGetHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetHook MimeNoContent Hook 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 RepoGetHook  
-- | @application/json@
instance Produces RepoGetHook MimeJSON


-- *** repoGetIssueConfig

-- | @GET \/repos\/{owner}\/{repo}\/issue_config@
-- 
-- Returns the issue config for a repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetIssueConfig
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
repoGetIssueConfig :: Owner
-> Repo
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
repoGetIssueConfig (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_config"]
    GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetIssueConfig MimeNoContent IssueConfig 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 RepoGetIssueConfig  
-- | @application/json@
instance Produces RepoGetIssueConfig MimeJSON


-- *** repoGetIssueTemplates

-- | @GET \/repos\/{owner}\/{repo}\/issue_templates@
-- 
-- Get available issue templates for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetIssueTemplates
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
repoGetIssueTemplates :: Owner
-> Repo
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
repoGetIssueTemplates (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_templates"]
    GiteaRequest
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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
  RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetIssueTemplates MimeNoContent [IssueTemplate] 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 RepoGetIssueTemplates  
-- | @application/json@
instance Produces RepoGetIssueTemplates MimeJSON


-- *** repoGetKey

-- | @GET \/repos\/{owner}\/{repo}\/keys\/{id}@
-- 
-- Get a repository's key by id
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetKey
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the key to get
  -> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
repoGetKey :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
repoGetKey (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey 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 RepoGetKey  
-- | @application/json@
instance Produces RepoGetKey MimeJSON


-- *** repoGetLanguages

-- | @GET \/repos\/{owner}\/{repo}\/languages@
-- 
-- Get languages and number of bytes of code written
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetLanguages
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetLanguages MimeNoContent ((Map.Map String Integer)) MimeJSON
repoGetLanguages :: Owner
-> Repo
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
repoGetLanguages (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/languages"]
    GiteaRequest
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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
  RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetLanguages MimeNoContent (Map FilePath Integer) 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 RepoGetLanguages  
-- | @application/json@
instance Produces RepoGetLanguages MimeJSON


-- *** repoGetLatestRelease

-- | @GET \/repos\/{owner}\/{repo}\/releases\/latest@
-- 
-- Gets the most recent non-prerelease, non-draft release of a repository, sorted by created_at
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetLatestRelease
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
repoGetLatestRelease :: Owner
-> Repo
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
repoGetLatestRelease (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/latest"]
    GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release 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 RepoGetLatestRelease  
-- | @application/json@
instance Produces RepoGetLatestRelease MimeJSON


-- *** repoGetLicenses

-- | @GET \/repos\/{owner}\/{repo}\/licenses@
-- 
-- Get repo licenses
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetLicenses
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
repoGetLicenses :: Owner
-> Repo
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
repoGetLicenses (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/licenses"]
    GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetLicenses 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 RepoGetLicenses  
-- | @application/json@
instance Produces RepoGetLicenses MimeJSON


-- *** repoGetNote

-- | @GET \/repos\/{owner}\/{repo}\/git\/notes\/{sha}@
-- 
-- Get a note corresponding to a single commit from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetNote
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  a git ref or commit sha
  -> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
repoGetNote :: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
repoGetNote (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/notes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetNote MimeNoContent Note 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 RepoGetNote  

-- | /Optional Param/ "verification" - include verification for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetNote Verification where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetNote contentType res accept
-> Verification -> GiteaRequest RepoGetNote contentType res accept
applyOptionalParam GiteaRequest RepoGetNote contentType res accept
req (Verification Bool
xs) =
    GiteaRequest RepoGetNote contentType res accept
req GiteaRequest RepoGetNote contentType res accept
-> [QueryItem] -> GiteaRequest RepoGetNote contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "files" - include a list of affected files for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetNote Files where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetNote contentType res accept
-> Files -> GiteaRequest RepoGetNote contentType res accept
applyOptionalParam GiteaRequest RepoGetNote contentType res accept
req (Files Bool
xs) =
    GiteaRequest RepoGetNote contentType res accept
req GiteaRequest RepoGetNote contentType res accept
-> [QueryItem] -> GiteaRequest RepoGetNote contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/json@
instance Produces RepoGetNote MimeJSON


-- *** repoGetPullRequest

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}@
-- 
-- Get a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullRequest
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to get
  -> GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
repoGetPullRequest :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest MimeJSON
repoGetPullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
    GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPullRequest MimeNoContent PullRequest 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 RepoGetPullRequest  
-- | @application/json@
instance Produces RepoGetPullRequest MimeJSON


-- *** repoGetPullRequestByBaseHead

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{base}\/{head}@
-- 
-- Get a pull request by base and head
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullRequestByBaseHead
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Base -- ^ "base" -  base of the pull request to get
  -> Head -- ^ "head" -  head of the pull request to get
  -> GiteaRequest RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
repoGetPullRequestByBaseHead :: Owner
-> Repo
-> Base
-> Head
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
repoGetPullRequestByBaseHead (Owner Text
owner) (Repo Text
repo) (Base Text
base) (Head Text
head) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
base,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
head]
    GiteaRequest
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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
  RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPullRequestByBaseHead MimeNoContent PullRequest 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 RepoGetPullRequestByBaseHead  
-- | @application/json@
instance Produces RepoGetPullRequestByBaseHead MimeJSON


-- *** repoGetPullRequestCommits

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/commits@
-- 
-- Get commits for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullRequestCommits
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to get
  -> GiteaRequest RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
repoGetPullRequestCommits :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
repoGetPullRequestCommits (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/commits"]
    GiteaRequest
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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
  RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPullRequestCommits MimeNoContent [Commit] 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 RepoGetPullRequestCommits  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetPullRequestCommits Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Page
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoGetPullRequestCommits Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Limit
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "verification" - include verification for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetPullRequestCommits Verification where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Verification
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Verification Bool
xs) =
    GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "files" - include a list of affected files for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetPullRequestCommits Files where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Files
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Files Bool
xs) =
    GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/json@
instance Produces RepoGetPullRequestCommits MimeJSON


-- *** repoGetPullRequestFiles

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/files@
-- 
-- Get changed files for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullRequestFiles
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to get
  -> GiteaRequest RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
repoGetPullRequestFiles :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
repoGetPullRequestFiles (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/files"]
    GiteaRequest
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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
  RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPullRequestFiles MimeNoContent [ChangedFile] 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 RepoGetPullRequestFiles  

-- | /Optional Param/ "skip-to" - skip to given file
instance HasOptionalParam RepoGetPullRequestFiles SkipTo where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> SkipTo
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (SkipTo Text
xs) =
    GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"skip-to", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "whitespace" - whitespace behavior
instance HasOptionalParam RepoGetPullRequestFiles Whitespace where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Whitespace
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Whitespace E'Whitespace
xs) =
    GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Whitespace) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"whitespace", E'Whitespace -> Maybe E'Whitespace
forall a. a -> Maybe a
Just E'Whitespace
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetPullRequestFiles Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Page
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoGetPullRequestFiles Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Limit
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoGetPullRequestFiles MimeJSON


-- *** repoGetPullReview

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}@
-- 
-- Get a specific review for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullReview
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
repoGetPullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
repoGetPullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview 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 RepoGetPullReview  
-- | @application/json@
instance Produces RepoGetPullReview MimeJSON


-- *** repoGetPullReviewComments

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}\/comments@
-- 
-- Get a specific review for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPullReviewComments
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoGetPullReviewComments MimeNoContent [PullReviewComment] MimeJSON
repoGetPullReviewComments :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     MimeJSON
repoGetPullReviewComments (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/comments"]
    GiteaRequest
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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
  RepoGetPullReviewComments
  MimeNoContent
  [PullReviewComment]
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPullReviewComments
     MimeNoContent
     [PullReviewComment]
     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 RepoGetPullReviewComments  
-- | @application/json@
instance Produces RepoGetPullReviewComments MimeJSON


-- *** repoGetPushMirrorByRemoteName

-- | @GET \/repos\/{owner}\/{repo}\/push_mirrors\/{name}@
-- 
-- Get push mirror of the repository by remoteName
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetPushMirrorByRemoteName
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Name -- ^ "name" -  remote name of push mirror
  -> GiteaRequest RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
repoGetPushMirrorByRemoteName :: Owner
-> Repo
-> Name
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
repoGetPushMirrorByRemoteName (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    GiteaRequest
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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
  RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetPushMirrorByRemoteName MimeNoContent PushMirror 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 RepoGetPushMirrorByRemoteName  
-- | @application/json@
instance Produces RepoGetPushMirrorByRemoteName MimeJSON


-- *** repoGetRawFile

-- | @GET \/repos\/{owner}\/{repo}\/raw\/{filepath}@
-- 
-- Get a file from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetRawFile
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the file to get, it should be \"{ref}/{filepath}\". If there is no ref could be inferred, it will be treated as the default branch
  -> GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
repoGetRawFile :: Owner
-> Repo
-> Filepath
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
repoGetRawFile (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/raw/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetRawFile MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFile  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag. Default the repository’s default branch
instance HasOptionalParam RepoGetRawFile Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetRawFile contentType res accept
-> Ref -> GiteaRequest RepoGetRawFile contentType res accept
applyOptionalParam GiteaRequest RepoGetRawFile contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoGetRawFile contentType res accept
req GiteaRequest RepoGetRawFile contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetRawFile contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/octet-stream@
instance Produces RepoGetRawFile MimeOctetStream


-- *** repoGetRawFileOrLFS

-- | @GET \/repos\/{owner}\/{repo}\/media\/{filepath}@
-- 
-- Get a file or it's LFS object from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetRawFileOrLFS
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the file to get, it should be \"{ref}/{filepath}\". If there is no ref could be inferred, it will be treated as the default branch
  -> GiteaRequest RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
repoGetRawFileOrLFS :: Owner
-> Repo
-> Filepath
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
repoGetRawFileOrLFS (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/media/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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
  RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
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 RepoGetRawFileOrLFS  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag. Default the repository’s default branch
instance HasOptionalParam RepoGetRawFileOrLFS Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetRawFileOrLFS contentType res accept
-> Ref -> GiteaRequest RepoGetRawFileOrLFS contentType res accept
applyOptionalParam GiteaRequest RepoGetRawFileOrLFS contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoGetRawFileOrLFS contentType res accept
req GiteaRequest RepoGetRawFileOrLFS contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetRawFileOrLFS contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/octet-stream@
instance Produces RepoGetRawFileOrLFS MimeOctetStream


-- *** repoGetRelease

-- | @GET \/repos\/{owner}\/{repo}\/releases\/{id}@
-- 
-- Get a release
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetRelease
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release to get
  -> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
repoGetRelease :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
repoGetRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetRelease MimeNoContent Release 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 RepoGetRelease  
-- | @application/json@
instance Produces RepoGetRelease MimeJSON


-- *** repoGetReleaseAttachment

-- | @GET \/repos\/{owner}\/{repo}\/releases\/{id}\/assets\/{attachment_id}@
-- 
-- Get a release attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetReleaseAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to get
  -> GiteaRequest RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
repoGetReleaseAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
repoGetReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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
  RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetReleaseAttachment MimeNoContent Attachment 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 RepoGetReleaseAttachment  
-- | @application/json@
instance Produces RepoGetReleaseAttachment MimeJSON


-- *** repoGetReleaseByTag

-- | @GET \/repos\/{owner}\/{repo}\/releases\/tags\/{tag}@
-- 
-- Get a release by tag name
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetReleaseByTag
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Tag2 -- ^ "tag" -  tag name of the release to get
  -> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
repoGetReleaseByTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
repoGetReleaseByTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
    GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release 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 RepoGetReleaseByTag  
-- | @application/json@
instance Produces RepoGetReleaseByTag MimeJSON


-- *** repoGetRepoPermissions

-- | @GET \/repos\/{owner}\/{repo}\/collaborators\/{collaborator}\/permission@
-- 
-- Get repository permissions for a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetRepoPermissions
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Collaborator -- ^ "collaborator" -  username of the collaborator
  -> GiteaRequest RepoGetRepoPermissions MimeNoContent RepoCollaboratorPermission MimeJSON
repoGetRepoPermissions :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     MimeJSON
repoGetRepoPermissions (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator,ByteString
"/permission"]
    GiteaRequest
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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
  RepoGetRepoPermissions
  MimeNoContent
  RepoCollaboratorPermission
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetRepoPermissions
     MimeNoContent
     RepoCollaboratorPermission
     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 RepoGetRepoPermissions  
-- | @application/json@
instance Produces RepoGetRepoPermissions MimeJSON


-- *** repoGetReviewers

-- | @GET \/repos\/{owner}\/{repo}\/reviewers@
-- 
-- Return all users that can be requested to review in this repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetReviewers
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
repoGetReviewers :: Owner
-> Repo
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
repoGetReviewers (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/reviewers"]
    GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] 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 RepoGetReviewers  
-- | @application/json@
instance Produces RepoGetReviewers MimeJSON


-- *** repoGetRunnerRegistrationToken

-- | @GET \/repos\/{owner}\/{repo}\/actions\/runners\/registration-token@
-- 
-- Get a repository's actions runner registration token
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetRunnerRegistrationToken
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
repoGetRunnerRegistrationToken :: Owner
-> Repo
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
repoGetRunnerRegistrationToken (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/runners/registration-token"]
    GiteaRequest
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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
  RepoGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
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 RepoGetRunnerRegistrationToken  
instance Produces RepoGetRunnerRegistrationToken MimeNoContent


-- *** repoGetSingleCommit

-- | @GET \/repos\/{owner}\/{repo}\/git\/commits\/{sha}@
-- 
-- Get a single commit from a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetSingleCommit
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  a git ref or commit sha
  -> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
repoGetSingleCommit :: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
repoGetSingleCommit (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit 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 RepoGetSingleCommit  

-- | /Optional Param/ "stat" - include diff stats for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetSingleCommit Stat where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Stat -> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Stat Bool
xs) =
    GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stat", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "verification" - include verification for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetSingleCommit Verification where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Verification
-> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Verification Bool
xs) =
    GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "files" - include a list of affected files for every commit (disable for speedup, default 'true')
instance HasOptionalParam RepoGetSingleCommit Files where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Files -> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Files Bool
xs) =
    GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/json@
instance Produces RepoGetSingleCommit MimeJSON


-- *** repoGetTag

-- | @GET \/repos\/{owner}\/{repo}\/tags\/{tag}@
-- 
-- Get the tag of a repository by tag name
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetTag
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Tag2 -- ^ "tag" -  name of tag
  -> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
repoGetTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
repoGetTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
    GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetTag MimeNoContent Tag 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 RepoGetTag  
-- | @application/json@
instance Produces RepoGetTag MimeJSON


-- *** repoGetTagProtection

-- | @GET \/repos\/{owner}\/{repo}\/tag_protections\/{id}@
-- 
-- Get a specific tag protection for the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetTagProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdInt -- ^ "id" -  id of the tag protect to get
  -> GiteaRequest RepoGetTagProtection MimeNoContent TagProtection MimeJSON
repoGetTagProtection :: Owner
-> Repo
-> IdInt
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection MimeJSON
repoGetTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    GiteaRequest
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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
  RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetTagProtection MimeNoContent TagProtection 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 RepoGetTagProtection  
-- | @application/json@
instance Produces RepoGetTagProtection MimeJSON


-- *** repoGetWikiPage

-- | @GET \/repos\/{owner}\/{repo}\/wiki\/page\/{pageName}@
-- 
-- Get a wiki page
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetWikiPage
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> PageName -- ^ "pageName" -  name of the page
  -> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
repoGetWikiPage :: Owner
-> Repo
-> PageName
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
repoGetWikiPage (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
  Method
-> [ByteString]
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
    GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage 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 RepoGetWikiPage  
-- | @application/json@
instance Produces RepoGetWikiPage MimeJSON


-- *** repoGetWikiPageRevisions

-- | @GET \/repos\/{owner}\/{repo}\/wiki\/revisions\/{pageName}@
-- 
-- Get revisions of a wiki page
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetWikiPageRevisions
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> PageName -- ^ "pageName" -  name of the page
  -> GiteaRequest RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
repoGetWikiPageRevisions :: Owner
-> Repo
-> PageName
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
repoGetWikiPageRevisions (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/revisions/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
    GiteaRequest
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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
  RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetWikiPageRevisions MimeNoContent WikiCommitList 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 RepoGetWikiPageRevisions  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetWikiPageRevisions Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPageRevisions contentType res accept
-> Page
-> GiteaRequest RepoGetWikiPageRevisions contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPageRevisions contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetWikiPageRevisions contentType res accept
req GiteaRequest RepoGetWikiPageRevisions contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPageRevisions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoGetWikiPageRevisions MimeJSON


-- *** repoGetWikiPages

-- | @GET \/repos\/{owner}\/{repo}\/wiki\/pages@
-- 
-- Get all wiki pages
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoGetWikiPages
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
repoGetWikiPages :: Owner
-> Repo
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
repoGetWikiPages (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/pages"]
    GiteaRequest
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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
  RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoGetWikiPages MimeNoContent [WikiPageMetaData] 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 RepoGetWikiPages  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoGetWikiPages Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPages contentType res accept
-> Page -> GiteaRequest RepoGetWikiPages contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPages contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoGetWikiPages contentType res accept
req GiteaRequest RepoGetWikiPages contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPages contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoGetWikiPages Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPages contentType res accept
-> Limit -> GiteaRequest RepoGetWikiPages contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPages contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoGetWikiPages contentType res accept
req GiteaRequest RepoGetWikiPages contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPages contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoGetWikiPages MimeJSON


-- *** repoListActionsSecrets

-- | @GET \/repos\/{owner}\/{repo}\/actions\/secrets@
-- 
-- List an repo's actions secrets
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListActionsSecrets
  :: Owner -- ^ "owner" -  owner of the repository
  -> Repo -- ^ "repo" -  name of the repository
  -> GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
repoListActionsSecrets :: Owner
-> Repo
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
repoListActionsSecrets (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets"]
    GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListActionsSecrets MimeNoContent [Secret] 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 RepoListActionsSecrets  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListActionsSecrets Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActionsSecrets contentType res accept
-> Page
-> GiteaRequest RepoListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest RepoListActionsSecrets contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListActionsSecrets contentType res accept
req GiteaRequest RepoListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActionsSecrets contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListActionsSecrets Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActionsSecrets contentType res accept
-> Limit
-> GiteaRequest RepoListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest RepoListActionsSecrets contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListActionsSecrets contentType res accept
req GiteaRequest RepoListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActionsSecrets contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListActionsSecrets MimeJSON


-- *** repoListActivityFeeds

-- | @GET \/repos\/{owner}\/{repo}\/activities\/feeds@
-- 
-- List a repository's activity feeds
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListActivityFeeds
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
repoListActivityFeeds :: Owner
-> Repo
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
repoListActivityFeeds (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/activities/feeds"]
    GiteaRequest
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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
  RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListActivityFeeds MimeNoContent [Activity] 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 RepoListActivityFeeds  

-- | /Optional Param/ "date" - the date of the activities to be found
instance HasOptionalParam RepoListActivityFeeds ParamDate where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> ParamDate
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (ParamDate Date
xs) =
    GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Date) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"date", Date -> Maybe Date
forall a. a -> Maybe a
Just Date
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListActivityFeeds Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> Page
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListActivityFeeds Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> Limit
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListActivityFeeds MimeJSON


-- *** repoListAllGitRefs

-- | @GET \/repos\/{owner}\/{repo}\/git\/refs@
-- 
-- Get specified ref or filtered repository's refs
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListAllGitRefs
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
repoListAllGitRefs :: Owner
-> Repo
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
repoListAllGitRefs (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/refs"]
    GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListAllGitRefs MimeNoContent [Reference] 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 RepoListAllGitRefs  
-- | @application/json@
instance Produces RepoListAllGitRefs MimeJSON


-- *** repoListBranchProtection

-- | @GET \/repos\/{owner}\/{repo}\/branch_protections@
-- 
-- List branch protections for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListBranchProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
repoListBranchProtection :: Owner
-> Repo
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
repoListBranchProtection (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections"]
    GiteaRequest
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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
  RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListBranchProtection MimeNoContent [BranchProtection] 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 RepoListBranchProtection  
-- | @application/json@
instance Produces RepoListBranchProtection MimeJSON


-- *** repoListBranches

-- | @GET \/repos\/{owner}\/{repo}\/branches@
-- 
-- List a repository's branches
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListBranches
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
repoListBranches :: Owner
-> Repo
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
repoListBranches (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches"]
    GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] 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 RepoListBranches  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListBranches Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListBranches contentType res accept
-> Page -> GiteaRequest RepoListBranches contentType res accept
applyOptionalParam GiteaRequest RepoListBranches contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListBranches contentType res accept
req GiteaRequest RepoListBranches contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListBranches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListBranches Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListBranches contentType res accept
-> Limit -> GiteaRequest RepoListBranches contentType res accept
applyOptionalParam GiteaRequest RepoListBranches contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListBranches contentType res accept
req GiteaRequest RepoListBranches contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListBranches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListBranches MimeJSON


-- *** repoListCollaborators

-- | @GET \/repos\/{owner}\/{repo}\/collaborators@
-- 
-- List a repository's collaborators
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListCollaborators
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
repoListCollaborators :: Owner
-> Repo
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
repoListCollaborators (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators"]
    GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] 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 RepoListCollaborators  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListCollaborators Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListCollaborators contentType res accept
-> Page
-> GiteaRequest RepoListCollaborators contentType res accept
applyOptionalParam GiteaRequest RepoListCollaborators contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListCollaborators contentType res accept
req GiteaRequest RepoListCollaborators contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListCollaborators contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListCollaborators Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListCollaborators contentType res accept
-> Limit
-> GiteaRequest RepoListCollaborators contentType res accept
applyOptionalParam GiteaRequest RepoListCollaborators contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListCollaborators contentType res accept
req GiteaRequest RepoListCollaborators contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListCollaborators contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListCollaborators MimeJSON


-- *** repoListGitHooks

-- | @GET \/repos\/{owner}\/{repo}\/hooks\/git@
-- 
-- List the Git hooks in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListGitHooks
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
repoListGitHooks :: Owner
-> Repo
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
repoListGitHooks (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git"]
    GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] 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 RepoListGitHooks  
-- | @application/json@
instance Produces RepoListGitHooks MimeJSON


-- *** repoListGitRefs

-- | @GET \/repos\/{owner}\/{repo}\/git\/refs\/{ref}@
-- 
-- Get specified ref or filtered repository's refs
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListGitRefs
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Ref -- ^ "ref" -  part or full name of the ref
  -> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
repoListGitRefs :: Owner
-> Repo
-> Ref
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
repoListGitRefs (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
  Method
-> [ByteString]
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/refs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref]
    GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] 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 RepoListGitRefs  
-- | @application/json@
instance Produces RepoListGitRefs MimeJSON


-- *** repoListHooks

-- | @GET \/repos\/{owner}\/{repo}\/hooks@
-- 
-- List the hooks in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListHooks
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
repoListHooks :: Owner
-> Repo -> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
repoListHooks (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks"]
    GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] 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 RepoListHooks  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListHooks Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListHooks contentType res accept
-> Page -> GiteaRequest RepoListHooks contentType res accept
applyOptionalParam GiteaRequest RepoListHooks contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListHooks contentType res accept
req GiteaRequest RepoListHooks contentType res accept
-> [QueryItem] -> GiteaRequest RepoListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListHooks Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListHooks contentType res accept
-> Limit -> GiteaRequest RepoListHooks contentType res accept
applyOptionalParam GiteaRequest RepoListHooks contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListHooks contentType res accept
req GiteaRequest RepoListHooks contentType res accept
-> [QueryItem] -> GiteaRequest RepoListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListHooks MimeJSON


-- *** repoListKeys

-- | @GET \/repos\/{owner}\/{repo}\/keys@
-- 
-- List a repository's keys
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListKeys
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
repoListKeys :: Owner
-> Repo
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
repoListKeys (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys"]
    GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] 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 RepoListKeys  

-- | /Optional Param/ "key_id" - the key_id to search for
instance HasOptionalParam RepoListKeys KeyId where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> KeyId -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (KeyId Int
xs) =
    GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"key_id", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "fingerprint" - fingerprint of the key
instance HasOptionalParam RepoListKeys Fingerprint where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Fingerprint -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Fingerprint Text
xs) =
    GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fingerprint", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListKeys Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Page -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListKeys Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Limit -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListKeys MimeJSON


-- *** repoListPinnedIssues

-- | @GET \/repos\/{owner}\/{repo}\/issues\/pinned@
-- 
-- List a repo's pinned issues
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListPinnedIssues
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
repoListPinnedIssues :: Owner
-> Repo
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
repoListPinnedIssues (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issues/pinned"]
    GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] 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 RepoListPinnedIssues  
-- | @application/json@
instance Produces RepoListPinnedIssues MimeJSON


-- *** repoListPinnedPullRequests

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/pinned@
-- 
-- List a repo's pinned pull requests
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListPinnedPullRequests
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPinnedPullRequests :: Owner
-> Repo
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPinnedPullRequests (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/pinned"]
    GiteaRequest
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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
  RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListPinnedPullRequests MimeNoContent [PullRequest] 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 RepoListPinnedPullRequests  
-- | @application/json@
instance Produces RepoListPinnedPullRequests MimeJSON


-- *** repoListPullRequests

-- | @GET \/repos\/{owner}\/{repo}\/pulls@
-- 
-- List a repo's pull requests
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListPullRequests
  :: Owner -- ^ "owner" -  Owner of the repo
  -> Repo -- ^ "repo" -  Name of the repo
  -> GiteaRequest RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPullRequests :: Owner
-> Repo
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPullRequests (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls"]
    GiteaRequest
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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
  RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListPullRequests MimeNoContent [PullRequest] 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 RepoListPullRequests  

-- | /Optional Param/ "state" - State of pull request
instance HasOptionalParam RepoListPullRequests State where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> State
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (State E'State2
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State2) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State2 -> Maybe E'State2
forall a. a -> Maybe a
Just E'State2
xs)

-- | /Optional Param/ "sort" - Type of sort
instance HasOptionalParam RepoListPullRequests Sort3 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Sort3
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Sort3 E'Sort2
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort2) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort2 -> Maybe E'Sort2
forall a. a -> Maybe a
Just E'Sort2
xs)

-- | /Optional Param/ "milestone" - ID of the milestone
instance HasOptionalParam RepoListPullRequests Milestone2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Milestone2
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Milestone2 Integer
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"milestone", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "labels" - Label IDs
instance HasOptionalParam RepoListPullRequests LabelsInteger where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> LabelsInteger
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (LabelsInteger [Integer]
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Integer]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"labels", [Integer] -> Maybe [Integer]
forall a. a -> Maybe a
Just [Integer]
xs)

-- | /Optional Param/ "poster" - Filter by pull request author
instance HasOptionalParam RepoListPullRequests Poster where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Poster
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Poster Text
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"poster", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "page" - Page number of results to return (1-based)
instance HasOptionalParam RepoListPullRequests Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Page -> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - Page size of results
instance HasOptionalParam RepoListPullRequests Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Limit
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListPullRequests MimeJSON


-- *** repoListPullReviews

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews@
-- 
-- List all reviews for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListPullReviews
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> GiteaRequest RepoListPullReviews MimeNoContent [PullReview] MimeJSON
repoListPullReviews :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] MimeJSON
repoListPullReviews (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews"]
    GiteaRequest
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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
  RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListPullReviews MimeNoContent [PullReview] 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 RepoListPullReviews  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListPullReviews Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullReviews contentType res accept
-> Page -> GiteaRequest RepoListPullReviews contentType res accept
applyOptionalParam GiteaRequest RepoListPullReviews contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListPullReviews contentType res accept
req GiteaRequest RepoListPullReviews contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullReviews contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListPullReviews Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullReviews contentType res accept
-> Limit -> GiteaRequest RepoListPullReviews contentType res accept
applyOptionalParam GiteaRequest RepoListPullReviews contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListPullReviews contentType res accept
req GiteaRequest RepoListPullReviews contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullReviews contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListPullReviews MimeJSON


-- *** repoListPushMirrors

-- | @GET \/repos\/{owner}\/{repo}\/push_mirrors@
-- 
-- Get all push mirrors of the repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListPushMirrors
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
repoListPushMirrors :: Owner
-> Repo
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
repoListPushMirrors (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors"]
    GiteaRequest
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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
  RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListPushMirrors MimeNoContent [PushMirror] 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 RepoListPushMirrors  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListPushMirrors Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPushMirrors contentType res accept
-> Page -> GiteaRequest RepoListPushMirrors contentType res accept
applyOptionalParam GiteaRequest RepoListPushMirrors contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListPushMirrors contentType res accept
req GiteaRequest RepoListPushMirrors contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPushMirrors contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListPushMirrors Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPushMirrors contentType res accept
-> Limit -> GiteaRequest RepoListPushMirrors contentType res accept
applyOptionalParam GiteaRequest RepoListPushMirrors contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListPushMirrors contentType res accept
req GiteaRequest RepoListPushMirrors contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPushMirrors contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListPushMirrors MimeJSON


-- *** repoListReleaseAttachments

-- | @GET \/repos\/{owner}\/{repo}\/releases\/{id}\/assets@
-- 
-- List release's attachments
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListReleaseAttachments
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the release
  -> GiteaRequest RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
repoListReleaseAttachments :: Owner
-> Repo
-> Id
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
repoListReleaseAttachments (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets"]
    GiteaRequest
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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
  RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListReleaseAttachments MimeNoContent [Attachment] 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 RepoListReleaseAttachments  
-- | @application/json@
instance Produces RepoListReleaseAttachments MimeJSON


-- *** repoListReleases

-- | @GET \/repos\/{owner}\/{repo}\/releases@
-- 
-- List a repo's releases
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListReleases
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
repoListReleases :: Owner
-> Repo
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
repoListReleases (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases"]
    GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] 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 RepoListReleases  

-- | /Optional Param/ "draft" - filter (exclude / include) drafts, if you dont have repo write access none will show
instance HasOptionalParam RepoListReleases Draft where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Draft -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Draft Bool
xs) =
    GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"draft", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "pre-release" - filter (exclude / include) pre-releases
instance HasOptionalParam RepoListReleases PreRelease where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> PreRelease
-> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (PreRelease Bool
xs) =
    GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pre-release", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListReleases Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Page -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListReleases Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Limit -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListReleases MimeJSON


-- *** repoListStargazers

-- | @GET \/repos\/{owner}\/{repo}\/stargazers@
-- 
-- List a repo's stargazers
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListStargazers
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
repoListStargazers :: Owner
-> Repo
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
repoListStargazers (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/stargazers"]
    GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] 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 RepoListStargazers  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListStargazers Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStargazers contentType res accept
-> Page -> GiteaRequest RepoListStargazers contentType res accept
applyOptionalParam GiteaRequest RepoListStargazers contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListStargazers contentType res accept
req GiteaRequest RepoListStargazers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStargazers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListStargazers Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStargazers contentType res accept
-> Limit -> GiteaRequest RepoListStargazers contentType res accept
applyOptionalParam GiteaRequest RepoListStargazers contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListStargazers contentType res accept
req GiteaRequest RepoListStargazers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStargazers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListStargazers MimeJSON


-- *** repoListStatuses

-- | @GET \/repos\/{owner}\/{repo}\/statuses\/{sha}@
-- 
-- Get a commit's statuses
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListStatuses
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Sha -- ^ "sha" -  sha of the commit
  -> GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
repoListStatuses :: Owner
-> Repo
-> Sha
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
repoListStatuses (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/statuses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
    GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListStatuses MimeNoContent [CommitStatus] 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 RepoListStatuses  

-- | /Optional Param/ "sort" - type of sort
instance HasOptionalParam RepoListStatuses Sort2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Sort2 -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Sort2 E'Sort
xs) =
    GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort -> Maybe E'Sort
forall a. a -> Maybe a
Just E'Sort
xs)

-- | /Optional Param/ "state" - type of state
instance HasOptionalParam RepoListStatuses State2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> State2 -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (State2 E'State3
xs) =
    GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State3 -> Maybe E'State3
forall a. a -> Maybe a
Just E'State3
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListStatuses Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Page -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListStatuses Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Limit -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListStatuses MimeJSON


-- *** repoListStatusesByRef

-- | @GET \/repos\/{owner}\/{repo}\/commits\/{ref}\/statuses@
-- 
-- Get a commit's statuses, by branch/tag/commit reference
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListStatusesByRef
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Ref -- ^ "ref" -  name of branch/tag/commit
  -> GiteaRequest RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
repoListStatusesByRef :: Owner
-> Repo
-> Ref
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
repoListStatusesByRef (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref,ByteString
"/statuses"]
    GiteaRequest
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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
  RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListStatusesByRef MimeNoContent [CommitStatus] 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 RepoListStatusesByRef  

-- | /Optional Param/ "sort" - type of sort
instance HasOptionalParam RepoListStatusesByRef Sort2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Sort2
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Sort2 E'Sort
xs) =
    GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort -> Maybe E'Sort
forall a. a -> Maybe a
Just E'Sort
xs)

-- | /Optional Param/ "state" - type of state
instance HasOptionalParam RepoListStatusesByRef State2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> State2
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (State2 E'State3
xs) =
    GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State3 -> Maybe E'State3
forall a. a -> Maybe a
Just E'State3
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListStatusesByRef Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Page
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListStatusesByRef Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Limit
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListStatusesByRef MimeJSON


-- *** repoListSubscribers

-- | @GET \/repos\/{owner}\/{repo}\/subscribers@
-- 
-- List a repo's watchers
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListSubscribers
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
repoListSubscribers :: Owner
-> Repo
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
repoListSubscribers (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscribers"]
    GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] 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 RepoListSubscribers  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListSubscribers Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListSubscribers contentType res accept
-> Page -> GiteaRequest RepoListSubscribers contentType res accept
applyOptionalParam GiteaRequest RepoListSubscribers contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListSubscribers contentType res accept
req GiteaRequest RepoListSubscribers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListSubscribers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListSubscribers Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListSubscribers contentType res accept
-> Limit -> GiteaRequest RepoListSubscribers contentType res accept
applyOptionalParam GiteaRequest RepoListSubscribers contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListSubscribers contentType res accept
req GiteaRequest RepoListSubscribers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListSubscribers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListSubscribers MimeJSON


-- *** repoListTagProtection

-- | @GET \/repos\/{owner}\/{repo}\/tag_protections@
-- 
-- List tag protections for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListTagProtection
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
repoListTagProtection :: Owner
-> Repo
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
repoListTagProtection (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections"]
    GiteaRequest
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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
  RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoListTagProtection MimeNoContent [TagProtection] 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 RepoListTagProtection  
-- | @application/json@
instance Produces RepoListTagProtection MimeJSON


-- *** repoListTags

-- | @GET \/repos\/{owner}\/{repo}\/tags@
-- 
-- List a repository's tags
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListTags
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
repoListTags :: Owner
-> Repo -> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
repoListTags (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags"]
    GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] 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 RepoListTags  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListTags Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTags contentType res accept
-> Page -> GiteaRequest RepoListTags contentType res accept
applyOptionalParam GiteaRequest RepoListTags contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListTags contentType res accept
req GiteaRequest RepoListTags contentType res accept
-> [QueryItem] -> GiteaRequest RepoListTags contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results, default maximum page size is 50
instance HasOptionalParam RepoListTags Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTags contentType res accept
-> Limit -> GiteaRequest RepoListTags contentType res accept
applyOptionalParam GiteaRequest RepoListTags contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListTags contentType res accept
req GiteaRequest RepoListTags contentType res accept
-> [QueryItem] -> GiteaRequest RepoListTags contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListTags MimeJSON


-- *** repoListTeams

-- | @GET \/repos\/{owner}\/{repo}\/teams@
-- 
-- List a repository's teams
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListTeams
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
repoListTeams :: Owner
-> Repo -> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
repoListTeams (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams"]
    GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] 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 RepoListTeams  
-- | @application/json@
instance Produces RepoListTeams MimeJSON


-- *** repoListTopics

-- | @GET \/repos\/{owner}\/{repo}\/topics@
-- 
-- Get list of topics that a repository has
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoListTopics
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
repoListTopics :: Owner
-> Repo
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
repoListTopics (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics"]
    GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName 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 RepoListTopics  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoListTopics Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTopics contentType res accept
-> Page -> GiteaRequest RepoListTopics contentType res accept
applyOptionalParam GiteaRequest RepoListTopics contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoListTopics contentType res accept
req GiteaRequest RepoListTopics contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListTopics contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoListTopics Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTopics contentType res accept
-> Limit -> GiteaRequest RepoListTopics contentType res accept
applyOptionalParam GiteaRequest RepoListTopics contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoListTopics contentType res accept
req GiteaRequest RepoListTopics contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListTopics contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoListTopics MimeJSON


-- *** repoMergePullRequest

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/merge@
-- 
-- Merge a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoMergePullRequest
  :: (Consumes RepoMergePullRequest contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to merge
  -> GiteaRequest RepoMergePullRequest contentType NoContent MimeNoContent
repoMergePullRequest :: forall contentType.
Consumes RepoMergePullRequest contentType =>
ContentType contentType
-> Owner
-> Repo
-> Index
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
repoMergePullRequest ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
    GiteaRequest
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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
  RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoMergePullRequest contentType NoContent MimeNoContent
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 RepoMergePullRequest 
instance HasBodyParam RepoMergePullRequest MergePullRequestOption 

-- | @application/json@
instance Consumes RepoMergePullRequest MimeJSON
-- | @text/plain@
instance Consumes RepoMergePullRequest MimePlainText

instance Produces RepoMergePullRequest MimeNoContent


-- *** repoMergeUpstream

-- | @POST \/repos\/{owner}\/{repo}\/merge-upstream@
-- 
-- Merge a branch from upstream
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoMergeUpstream
  :: (Consumes RepoMergeUpstream contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
repoMergeUpstream :: forall contentType.
Consumes RepoMergeUpstream contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
repoMergeUpstream ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/merge-upstream"]
    GiteaRequest
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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
  RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoMergeUpstream contentType MergeUpstreamResponse 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 RepoMergeUpstream 
instance HasBodyParam RepoMergeUpstream MergeUpstreamRequest 

-- | @application/json@
instance Consumes RepoMergeUpstream MimeJSON
-- | @text/plain@
instance Consumes RepoMergeUpstream MimePlainText

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


-- *** repoMigrate

-- | @POST \/repos\/migrate@
-- 
-- Migrate a remote git repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoMigrate
  :: (Consumes RepoMigrate MimeJSON)
  => GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
repoMigrate :: Consumes RepoMigrate MimeJSON =>
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
repoMigrate =
  Method
-> [ByteString]
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/migrate"]
    GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoMigrate MimeJSON Repository 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 RepoMigrate 
instance HasBodyParam RepoMigrate MigrateRepoOptions 

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

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


-- *** repoMirrorSync

-- | @POST \/repos\/{owner}\/{repo}\/mirror-sync@
-- 
-- Sync a mirrored repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoMirrorSync
  :: Owner -- ^ "owner" -  owner of the repo to sync
  -> Repo -- ^ "repo" -  name of the repo to sync
  -> GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
repoMirrorSync :: Owner
-> Repo
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
repoMirrorSync (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/mirror-sync"]
    GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoMirrorSync  
instance Produces RepoMirrorSync MimeNoContent


-- *** repoNewPinAllowed

-- | @GET \/repos\/{owner}\/{repo}\/new_pin_allowed@
-- 
-- Returns if new Issue Pins are allowed
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoNewPinAllowed
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
repoNewPinAllowed :: Owner
-> Repo
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
repoNewPinAllowed (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/new_pin_allowed"]
    GiteaRequest
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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
  RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed 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 RepoNewPinAllowed  
-- | @application/json@
instance Produces RepoNewPinAllowed MimeJSON


-- *** repoPullRequestIsMerged

-- | @GET \/repos\/{owner}\/{repo}\/pulls\/{index}\/merge@
-- 
-- Check if a pull request has been merged
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoPullRequestIsMerged
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> GiteaRequest RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
repoPullRequestIsMerged :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
repoPullRequestIsMerged (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
    GiteaRequest
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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
  RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
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 RepoPullRequestIsMerged  
instance Produces RepoPullRequestIsMerged MimeNoContent


-- *** repoPushMirrorSync

-- | @POST \/repos\/{owner}\/{repo}\/push_mirrors-sync@
-- 
-- Sync all push mirrored repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoPushMirrorSync
  :: Owner -- ^ "owner" -  owner of the repo to sync
  -> Repo -- ^ "repo" -  name of the repo to sync
  -> GiteaRequest RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
repoPushMirrorSync :: Owner
-> Repo
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
repoPushMirrorSync (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors-sync"]
    GiteaRequest
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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
  RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
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 RepoPushMirrorSync  
instance Produces RepoPushMirrorSync MimeNoContent


-- *** repoSearch

-- | @GET \/repos\/search@
-- 
-- Search for repositories
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoSearch
  :: GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
repoSearch :: GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
repoSearch =
  Method
-> [ByteString]
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/search"]
    GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults 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 RepoSearch  

-- | /Optional Param/ "q" - keyword
instance HasOptionalParam RepoSearch Q where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Q -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Q Text
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"q", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "topic" - Limit search to repositories with keyword as topic
instance HasOptionalParam RepoSearch Topic where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Topic -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Topic Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"topic", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "includeDesc" - include search of keyword within repository description
instance HasOptionalParam RepoSearch IncludeDesc where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> IncludeDesc -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (IncludeDesc Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"includeDesc", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "uid" - search only for repos that the user with the given id owns or contributes to
instance HasOptionalParam RepoSearch Uid where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Uid -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Uid Integer
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"uid", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "priority_owner_id" - repo owner to prioritize in the results
instance HasOptionalParam RepoSearch PriorityOwnerId where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> PriorityOwnerId
-> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (PriorityOwnerId Integer
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"priority_owner_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "team_id" - search only for repos that belong to the given team id
instance HasOptionalParam RepoSearch TeamId where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> TeamId -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (TeamId Integer
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"team_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "starredBy" - search only for repos that the user with the given id has starred
instance HasOptionalParam RepoSearch StarredBy where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> StarredBy -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (StarredBy Integer
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"starredBy", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "private" - include private repositories this user has access to (defaults to true)
instance HasOptionalParam RepoSearch Private where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Private -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Private Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"private", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "is_private" - show only pubic, private or all repositories (defaults to all)
instance HasOptionalParam RepoSearch IsPrivate where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> IsPrivate -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (IsPrivate Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"is_private", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "template" - include template repositories this user has access to (defaults to true)
instance HasOptionalParam RepoSearch Template where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Template -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Template Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"template", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "archived" - show only archived, non-archived or all repositories (defaults to all)
instance HasOptionalParam RepoSearch Archived where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Archived -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Archived Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"archived", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "mode" - type of repository to search for. Supported values are \"fork\", \"source\", \"mirror\" and \"collaborative\"
instance HasOptionalParam RepoSearch Mode where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Mode -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Mode Text
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"mode", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "exclusive" - if `uid` is given, search only for repos that the user owns
instance HasOptionalParam RepoSearch Exclusive where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Exclusive -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Exclusive Bool
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"exclusive", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "sort" - sort repos by attribute. Supported values are \"alpha\", \"created\", \"updated\", \"size\", \"git_size\", \"lfs_size\", \"stars\", \"forks\" and \"id\". Default is \"alpha\"
instance HasOptionalParam RepoSearch Sort where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Sort -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Sort Text
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "order" - sort order, either \"asc\" (ascending) or \"desc\" (descending). Default is \"asc\", ignored if \"sort\" is not specified.
instance HasOptionalParam RepoSearch Order where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Order -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Order Text
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"order", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoSearch Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Page -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoSearch Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Limit -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoSearch MimeJSON


-- *** repoSigningKey

-- | @GET \/repos\/{owner}\/{repo}\/signing-key.gpg@
-- 
-- Get signing-key.gpg for given repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoSigningKey
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
repoSigningKey :: Owner
-> Repo
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
repoSigningKey (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/signing-key.gpg"]
    GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoSigningKey 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 RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoSigningKey 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 RepoSigningKey  
-- | @text/plain@
instance Produces RepoSigningKey MimePlainText


-- *** repoSubmitPullReview

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}@
-- 
-- Submit a pending review to an pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoSubmitPullReview
  :: (Consumes RepoSubmitPullReview contentType, MimeRender contentType SubmitPullReviewOptions)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> SubmitPullReviewOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
repoSubmitPullReview :: forall contentType.
(Consumes RepoSubmitPullReview contentType,
 MimeRender contentType SubmitPullReviewOptions) =>
ContentType contentType
-> SubmitPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview MimeJSON
repoSubmitPullReview ContentType contentType
_ SubmitPullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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 RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview 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)
    GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> SubmitPullReviewOptions
-> GiteaRequest
     RepoSubmitPullReview contentType PullReview MimeJSON
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 RepoSubmitPullReview contentType,
 MimeRender contentType SubmitPullReviewOptions) =>
GiteaRequest RepoSubmitPullReview contentType res accept
-> SubmitPullReviewOptions
-> GiteaRequest RepoSubmitPullReview contentType res accept
`setBodyParam` SubmitPullReviewOptions
body

data RepoSubmitPullReview 
instance HasBodyParam RepoSubmitPullReview SubmitPullReviewOptions 

-- | @application/json@
instance Consumes RepoSubmitPullReview MimeJSON
-- | @text/plain@
instance Consumes RepoSubmitPullReview MimePlainText

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


-- *** repoTestHook

-- | @POST \/repos\/{owner}\/{repo}\/hooks\/{id}\/tests@
-- 
-- Test a push webhook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoTestHook
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the hook to test
  -> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
repoTestHook :: Owner
-> Repo
-> Id
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
repoTestHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/tests"]
    GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
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 RepoTestHook  

-- | /Optional Param/ "ref" - The name of the commit/branch/tag, indicates which commit will be loaded to the webhook payload.
instance HasOptionalParam RepoTestHook Ref where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTestHook contentType res accept
-> Ref -> GiteaRequest RepoTestHook contentType res accept
applyOptionalParam GiteaRequest RepoTestHook contentType res accept
req (Ref Text
xs) =
    GiteaRequest RepoTestHook contentType res accept
req GiteaRequest RepoTestHook contentType res accept
-> [QueryItem] -> GiteaRequest RepoTestHook contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoTestHook MimeNoContent


-- *** repoTrackedTimes

-- | @GET \/repos\/{owner}\/{repo}\/times@
-- 
-- List a repo's tracked times
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoTrackedTimes
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
repoTrackedTimes :: Owner
-> Repo
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
repoTrackedTimes (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/times"]
    GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoTrackedTimes MimeNoContent [TrackedTime] 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 RepoTrackedTimes  

-- | /Optional Param/ "user" - optional filter by user (available for issue managers)
instance HasOptionalParam RepoTrackedTimes User2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> User2 -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (User2 Text
xs) =
    GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"user", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "since" - Only show times updated after the given time. This is a timestamp in RFC 3339 format
instance HasOptionalParam RepoTrackedTimes Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Since -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Since DateTime
xs) =
    GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"since", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)

-- | /Optional Param/ "before" - Only show times updated before the given time. This is a timestamp in RFC 3339 format
instance HasOptionalParam RepoTrackedTimes Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Before -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Before DateTime
xs) =
    GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"before", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam RepoTrackedTimes Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Page -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Page Int
xs) =
    GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam RepoTrackedTimes Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Limit -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Limit Int
xs) =
    GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces RepoTrackedTimes MimeJSON


-- *** repoTransfer0

-- | @POST \/repos\/{owner}\/{repo}\/transfer@
-- 
-- Transfer a repo ownership
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoTransfer0
  :: (Consumes RepoTransfer0 contentType, MimeRender contentType TransferRepoOption)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> TransferRepoOption -- ^ "body" -  Transfer Options
  -> Owner -- ^ "owner" -  owner of the repo to transfer
  -> Repo -- ^ "repo" -  name of the repo to transfer
  -> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
repoTransfer0 :: forall contentType.
(Consumes RepoTransfer0 contentType,
 MimeRender contentType TransferRepoOption) =>
ContentType contentType
-> TransferRepoOption
-> Owner
-> Repo
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
repoTransfer0 ContentType contentType
_ TransferRepoOption
body (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer"]
    GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoTransfer0 contentType Repository 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 RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoTransfer0 contentType Repository 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)
    GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> TransferRepoOption
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
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 RepoTransfer0 contentType,
 MimeRender contentType TransferRepoOption) =>
GiteaRequest RepoTransfer0 contentType res accept
-> TransferRepoOption
-> GiteaRequest RepoTransfer0 contentType res accept
`setBodyParam` TransferRepoOption
body

data RepoTransfer0 

-- | /Body Param/ "body" - Transfer Options
instance HasBodyParam RepoTransfer0 TransferRepoOption 

-- | @application/json@
instance Consumes RepoTransfer0 MimeJSON
-- | @text/plain@
instance Consumes RepoTransfer0 MimePlainText

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


-- *** repoUnDismissPullReview

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/reviews\/{id}\/undismissals@
-- 
-- Cancel to dismiss a review for a pull request
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUnDismissPullReview
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request
  -> Id -- ^ "id" -  id of the review
  -> GiteaRequest RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
repoUnDismissPullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
repoUnDismissPullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/undismissals"]
    GiteaRequest
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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
  RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoUnDismissPullReview MimeNoContent PullReview 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 RepoUnDismissPullReview  
-- | @application/json@
instance Produces RepoUnDismissPullReview MimeJSON


-- *** repoUpdateAvatar

-- | @POST \/repos\/{owner}\/{repo}\/avatar@
-- 
-- Update avatar
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdateAvatar
  :: (Consumes RepoUpdateAvatar contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
repoUpdateAvatar :: forall contentType.
Consumes RepoUpdateAvatar contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
repoUpdateAvatar ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/avatar"]
    GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoUpdateAvatar contentType NoContent MimeNoContent
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 RepoUpdateAvatar 
instance HasBodyParam RepoUpdateAvatar UpdateRepoAvatarOption 

-- | @application/json@
instance Consumes RepoUpdateAvatar MimeJSON
-- | @text/plain@
instance Consumes RepoUpdateAvatar MimePlainText

instance Produces RepoUpdateAvatar MimeNoContent


-- *** repoUpdateBranch

-- | @PATCH \/repos\/{owner}\/{repo}\/branches\/{branch}@
-- 
-- Update a branch
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdateBranch
  :: (Consumes RepoUpdateBranch MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Branch2 -- ^ "branch" -  name of the branch
  -> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
repoUpdateBranch :: Consumes RepoUpdateBranch MimeJSON =>
Owner
-> Repo
-> Branch2
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
repoUpdateBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
  Method
-> [ByteString]
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
    GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
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 RepoUpdateBranch 
instance HasBodyParam RepoUpdateBranch UpdateBranchRepoOption 

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

instance Produces RepoUpdateBranch MimeNoContent


-- *** repoUpdateBranchProtectionPriories

-- | @POST \/repos\/{owner}\/{repo}\/branch_protections\/priority@
-- 
-- Update the priorities of branch protections for a repository.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdateBranchProtectionPriories
  :: (Consumes RepoUpdateBranchProtectionPriories MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
repoUpdateBranchProtectionPriories :: Consumes RepoUpdateBranchProtectionPriories MimeJSON =>
Owner
-> Repo
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
repoUpdateBranchProtectionPriories (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/priority"]
    GiteaRequest
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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
  RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
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 RepoUpdateBranchProtectionPriories 
instance HasBodyParam RepoUpdateBranchProtectionPriories UpdateBranchProtectionPriories 

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

instance Produces RepoUpdateBranchProtectionPriories MimeNoContent


-- *** repoUpdateFile

-- | @PUT \/repos\/{owner}\/{repo}\/contents\/{filepath}@
-- 
-- Update a file in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdateFile
  :: (Consumes RepoUpdateFile MimeJSON, MimeRender MimeJSON UpdateFileOptions)
  => UpdateFileOptions -- ^ "body"
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Filepath -- ^ "filepath" -  path of the file to update
  -> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
repoUpdateFile :: (Consumes RepoUpdateFile MimeJSON,
 MimeRender MimeJSON UpdateFileOptions) =>
UpdateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
repoUpdateFile UpdateFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
  Method
-> [ByteString]
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
    GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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 RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse 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)
    GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> UpdateFileOptions
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
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 RepoUpdateFile contentType,
 MimeRender contentType UpdateFileOptions) =>
GiteaRequest RepoUpdateFile contentType res accept
-> UpdateFileOptions
-> GiteaRequest RepoUpdateFile contentType res accept
`setBodyParam` UpdateFileOptions
body

data RepoUpdateFile 
instance HasBodyParam RepoUpdateFile UpdateFileOptions 

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

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


-- *** repoUpdatePullRequest

-- | @POST \/repos\/{owner}\/{repo}\/pulls\/{index}\/update@
-- 
-- Merge PR's baseBranch into headBranch
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdatePullRequest
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the pull request to get
  -> GiteaRequest RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
repoUpdatePullRequest :: Owner
-> Repo
-> Index
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
repoUpdatePullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/update"]
    GiteaRequest
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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
  RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
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 RepoUpdatePullRequest  

-- | /Optional Param/ "style" - how to update pull request
instance HasOptionalParam RepoUpdatePullRequest Style where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoUpdatePullRequest contentType res accept
-> Style
-> GiteaRequest RepoUpdatePullRequest contentType res accept
applyOptionalParam GiteaRequest RepoUpdatePullRequest contentType res accept
req (Style E'Style
xs) =
    GiteaRequest RepoUpdatePullRequest contentType res accept
req GiteaRequest RepoUpdatePullRequest contentType res accept
-> [QueryItem]
-> GiteaRequest RepoUpdatePullRequest contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Style) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"style", E'Style -> Maybe E'Style
forall a. a -> Maybe a
Just E'Style
xs)
instance Produces RepoUpdatePullRequest MimeNoContent


-- *** repoUpdateTopics

-- | @PUT \/repos\/{owner}\/{repo}\/topics@
-- 
-- Replace list of topics for a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoUpdateTopics
  :: (Consumes RepoUpdateTopics contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
repoUpdateTopics :: forall contentType.
Consumes RepoUpdateTopics contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
repoUpdateTopics ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics"]
    GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoUpdateTopics contentType NoContent MimeNoContent
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 RepoUpdateTopics 
instance HasBodyParam RepoUpdateTopics RepoTopicOptions 

-- | @application/json@
instance Consumes RepoUpdateTopics MimeJSON
-- | @text/plain@
instance Consumes RepoUpdateTopics MimePlainText

instance Produces RepoUpdateTopics MimeNoContent


-- *** repoValidateIssueConfig

-- | @GET \/repos\/{owner}\/{repo}\/issue_config\/validate@
-- 
-- Returns the validation information for a issue config
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
repoValidateIssueConfig
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest RepoValidateIssueConfig MimeNoContent IssueConfigValidation MimeJSON
repoValidateIssueConfig :: Owner
-> Repo
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     MimeJSON
repoValidateIssueConfig (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_config/validate"]
    GiteaRequest
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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
  RepoValidateIssueConfig
  MimeNoContent
  IssueConfigValidation
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     RepoValidateIssueConfig
     MimeNoContent
     IssueConfigValidation
     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 RepoValidateIssueConfig  
-- | @application/json@
instance Produces RepoValidateIssueConfig MimeJSON


-- *** topicSearch

-- | @GET \/topics\/search@
-- 
-- search topics via keyword
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
topicSearch
  :: Q -- ^ "q" -  keywords to search
  -> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
topicSearch :: Q
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
topicSearch (Q Text
q) =
  Method
-> [ByteString]
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/topics/search"]
    GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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 TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] 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)
    GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> [QueryItem]
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"q", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
q)

data TopicSearch  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam TopicSearch Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest TopicSearch contentType res accept
-> Page -> GiteaRequest TopicSearch contentType res accept
applyOptionalParam GiteaRequest TopicSearch contentType res accept
req (Page Int
xs) =
    GiteaRequest TopicSearch contentType res accept
req GiteaRequest TopicSearch contentType res accept
-> [QueryItem] -> GiteaRequest TopicSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "limit" - page size of results
instance HasOptionalParam TopicSearch Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest TopicSearch contentType res accept
-> Limit -> GiteaRequest TopicSearch contentType res accept
applyOptionalParam GiteaRequest TopicSearch contentType res accept
req (Limit Int
xs) =
    GiteaRequest TopicSearch contentType res accept
req GiteaRequest TopicSearch contentType res accept
-> [QueryItem] -> GiteaRequest TopicSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces TopicSearch MimeJSON


-- *** updateRepoSecret

-- | @PUT \/repos\/{owner}\/{repo}\/actions\/secrets\/{secretname}@
-- 
-- Create or Update a secret value in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
updateRepoSecret
  :: (Consumes UpdateRepoSecret MimeJSON)
  => Owner -- ^ "owner" -  owner of the repository
  -> Repo -- ^ "repo" -  name of the repository
  -> Secretname -- ^ "secretname" -  name of the secret
  -> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
updateRepoSecret :: Consumes UpdateRepoSecret MimeJSON =>
Owner
-> Repo
-> Secretname
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
updateRepoSecret (Owner Text
owner) (Repo Text
repo) (Secretname Text
secretname) =
  Method
-> [ByteString]
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
    GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
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 UpdateRepoSecret 
instance HasBodyParam UpdateRepoSecret CreateOrUpdateSecretOption 

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

instance Produces UpdateRepoSecret MimeNoContent


-- *** updateRepoVariable

-- | @PUT \/repos\/{owner}\/{repo}\/actions\/variables\/{variablename}@
-- 
-- Update a repo-level variable
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
updateRepoVariable
  :: (Consumes UpdateRepoVariable contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  name of the owner
  -> Repo -- ^ "repo" -  name of the repository
  -> Variablename -- ^ "variablename" -  name of the variable
  -> GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
updateRepoVariable :: forall contentType.
Consumes UpdateRepoVariable contentType =>
ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
updateRepoVariable ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
  Method
-> [ByteString]
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
    GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     UpdateRepoVariable contentType NoContent MimeNoContent
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 UpdateRepoVariable 
instance HasBodyParam UpdateRepoVariable UpdateVariableOption 

-- | @application/json@
instance Consumes UpdateRepoVariable MimeJSON
-- | @text/plain@
instance Consumes UpdateRepoVariable MimePlainText

instance Produces UpdateRepoVariable MimeNoContent


-- *** userCurrentCheckSubscription

-- | @GET \/repos\/{owner}\/{repo}\/subscription@
-- 
-- Check if the current user is watching a repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
userCurrentCheckSubscription
  :: Accept accept -- ^ request accept ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest UserCurrentCheckSubscription MimeNoContent WatchInfo accept
userCurrentCheckSubscription :: forall accept.
Accept accept
-> Owner
-> Repo
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
userCurrentCheckSubscription  Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
    GiteaRequest
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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
  UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyToken
-> GiteaRequest
     UserCurrentCheckSubscription MimeNoContent WatchInfo accept
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 UserCurrentCheckSubscription  
-- | @text/html@
instance Produces UserCurrentCheckSubscription MimeTextHtml
-- | @application/json@
instance Produces UserCurrentCheckSubscription MimeJSON


-- *** userCurrentDeleteSubscription

-- | @DELETE \/repos\/{owner}\/{repo}\/subscription@
-- 
-- Unwatch a repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
userCurrentDeleteSubscription
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
userCurrentDeleteSubscription :: Owner
-> Repo
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
userCurrentDeleteSubscription (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
    GiteaRequest
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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
  UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
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 UserCurrentDeleteSubscription  
instance Produces UserCurrentDeleteSubscription MimeNoContent


-- *** userCurrentPutSubscription

-- | @PUT \/repos\/{owner}\/{repo}\/subscription@
-- 
-- Watch a repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
userCurrentPutSubscription
  :: Accept accept -- ^ request accept ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest UserCurrentPutSubscription MimeNoContent WatchInfo accept
userCurrentPutSubscription :: forall accept.
Accept accept
-> Owner
-> Repo
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
userCurrentPutSubscription  Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
    GiteaRequest
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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
  UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyToken
-> GiteaRequest
     UserCurrentPutSubscription MimeNoContent WatchInfo accept
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 UserCurrentPutSubscription  
-- | @text/html@
instance Produces UserCurrentPutSubscription MimeTextHtml
-- | @application/json@
instance Produces UserCurrentPutSubscription MimeJSON


-- *** userTrackedTimes

-- | @GET \/repos\/{owner}\/{repo}\/times\/{user}@
-- 
-- List a user's tracked times in a repo
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
userTrackedTimes
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> User2 -- ^ "user" -  username of user
  -> GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userTrackedTimes :: Owner
-> Repo
-> User2
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userTrackedTimes (Owner Text
owner) (Repo Text
repo) (User2 Text
user) =
  Method
-> [ByteString]
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/times/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
user]
    GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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 UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     UserTrackedTimes MimeNoContent [TrackedTime] 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)

{-# DEPRECATED userTrackedTimes "" #-}

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