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

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


-- ** Issue

-- *** issueAddLabel

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/labels@
-- 
-- Add a label to an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueAddLabel
  :: (Consumes IssueAddLabel MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueAddLabel MimeJSON [Label] MimeJSON
issueAddLabel :: Consumes IssueAddLabel MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssueAddLabel MimeJSON [Label] MimeJSON
issueAddLabel (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/labels"]
    GiteaRequest IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueAddLabel MimeJSON [Label] 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 IssueAddLabel 
instance HasBodyParam IssueAddLabel IssueLabelsOption 

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

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


-- *** issueAddSubscription

-- | @PUT \/repos\/{owner}\/{repo}\/issues\/{index}\/subscriptions\/{user}@
-- 
-- Subscribe user to issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueAddSubscription
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> User2 -- ^ "user" -  user to subscribe
  -> GiteaRequest IssueAddSubscription MimeNoContent NoContent MimeNoContent
issueAddSubscription :: Owner
-> Repo
-> Index
-> User2
-> GiteaRequest
     IssueAddSubscription MimeNoContent NoContent MimeNoContent
issueAddSubscription (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (User2 Text
user) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueAddSubscription 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/subscriptions/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
user]
    GiteaRequest
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueAddSubscription 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
  IssueAddSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueAddSubscription 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 IssueAddSubscription  
instance Produces IssueAddSubscription MimeNoContent


-- *** issueAddTime

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/times@
-- 
-- Add tracked time to a issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueAddTime
  :: (Consumes IssueAddTime MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueAddTime MimeJSON TrackedTime MimeJSON
issueAddTime :: Consumes IssueAddTime MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssueAddTime MimeJSON TrackedTime MimeJSON
issueAddTime (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueAddTime MimeJSON TrackedTime 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/times"]
    GiteaRequest IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime MimeJSON TrackedTime MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueAddTime MimeJSON 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 IssueAddTime 
instance HasBodyParam IssueAddTime AddTimeOption 

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

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


-- *** issueCheckSubscription

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/subscriptions\/check@
-- 
-- Check if user is subscribed to an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCheckSubscription
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
issueCheckSubscription :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
issueCheckSubscription (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/subscriptions/check"]
    GiteaRequest
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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
  IssueCheckSubscription MimeNoContent WatchInfo MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueCheckSubscription MimeNoContent WatchInfo 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 IssueCheckSubscription  
-- | @application/json@
instance Produces IssueCheckSubscription MimeJSON


-- *** issueClearLabels

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/labels@
-- 
-- Remove all labels from an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueClearLabels
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueClearLabels MimeNoContent NoContent MimeNoContent
issueClearLabels :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueClearLabels MimeNoContent NoContent MimeNoContent
issueClearLabels (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueClearLabels 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/labels"]
    GiteaRequest IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueClearLabels 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 IssueClearLabels  
instance Produces IssueClearLabels MimeNoContent


-- *** issueCreateComment

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/comments@
-- 
-- Add a comment to an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateComment
  :: (Consumes IssueCreateComment MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueCreateComment MimeJSON Comment MimeJSON
issueCreateComment :: Consumes IssueCreateComment MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssueCreateComment MimeJSON Comment MimeJSON
issueCreateComment (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueCreateComment MimeJSON Comment 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/comments"]
    GiteaRequest IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueCreateComment MimeJSON Comment 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 IssueCreateComment 
instance HasBodyParam IssueCreateComment CreateIssueCommentOption 

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

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


-- *** issueCreateIssue

-- | @POST \/repos\/{owner}\/{repo}\/issues@
-- 
-- Create an issue. If using deadline only the date will be taken into account, and time of day ignored.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateIssue
  :: (Consumes IssueCreateIssue MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueCreateIssue MimeJSON Issue MimeJSON
issueCreateIssue :: Consumes IssueCreateIssue MimeJSON =>
Owner
-> Repo -> GiteaRequest IssueCreateIssue MimeJSON Issue MimeJSON
issueCreateIssue (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest IssueCreateIssue MimeJSON Issue 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
"/issues"]
    GiteaRequest IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueCreateIssue MimeJSON 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 IssueCreateIssue 
instance HasBodyParam IssueCreateIssue CreateIssueOption 

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

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


-- *** issueCreateIssueAttachment

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/assets@
-- 
-- Create an issue attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateIssueAttachment
  :: (Consumes IssueCreateIssueAttachment MimeMultipartFormData)
  => Attachment2 -- ^ "attachment" -  attachment to upload
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueCreateIssueAttachment MimeMultipartFormData Attachment MimeJSON
issueCreateIssueAttachment :: Consumes IssueCreateIssueAttachment MimeMultipartFormData =>
Attachment2
-> Owner
-> Repo
-> Index
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     Attachment
     MimeJSON
issueCreateIssueAttachment (Attachment2 FilePath
attachment) (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/assets"]
    GiteaRequest
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     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)
    GiteaRequest
  IssueCreateIssueAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Part
-> GiteaRequest
     IssueCreateIssueAttachment
     MimeMultipartFormData
     Attachment
     MimeJSON
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
attachment

data IssueCreateIssueAttachment  

-- | /Optional Param/ "name" - name of the attachment
instance HasOptionalParam IssueCreateIssueAttachment Name where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueCreateIssueAttachment contentType res accept
-> Name
-> GiteaRequest IssueCreateIssueAttachment contentType res accept
applyOptionalParam GiteaRequest IssueCreateIssueAttachment contentType res accept
req (Name Text
xs) =
    GiteaRequest IssueCreateIssueAttachment contentType res accept
req GiteaRequest IssueCreateIssueAttachment contentType res accept
-> [QueryItem]
-> GiteaRequest IssueCreateIssueAttachment 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)

-- | @multipart/form-data@
instance Consumes IssueCreateIssueAttachment MimeMultipartFormData

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


-- *** issueCreateIssueBlocking

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/blocks@
-- 
-- Block the issue given in the body by the issue in path
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateIssueBlocking
  :: (Consumes IssueCreateIssueBlocking contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueCreateIssueBlocking contentType Issue MimeJSON
issueCreateIssueBlocking :: forall contentType.
Consumes IssueCreateIssueBlocking contentType =>
ContentType contentType
-> Owner
-> Repo
-> IndexText
-> GiteaRequest IssueCreateIssueBlocking contentType Issue MimeJSON
issueCreateIssueBlocking ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueCreateIssueBlocking contentType Issue 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
"/issues/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/blocks"]
    GiteaRequest IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueCreateIssueBlocking contentType 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 IssueCreateIssueBlocking 
instance HasBodyParam IssueCreateIssueBlocking IssueMeta 

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

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


-- *** issueCreateIssueCommentAttachment

-- | @POST \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/assets@
-- 
-- Create a comment attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateIssueCommentAttachment
  :: (Consumes IssueCreateIssueCommentAttachment MimeMultipartFormData)
  => Attachment2 -- ^ "attachment" -  attachment to upload
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment
  -> GiteaRequest IssueCreateIssueCommentAttachment MimeMultipartFormData Attachment MimeJSON
issueCreateIssueCommentAttachment :: Consumes IssueCreateIssueCommentAttachment MimeMultipartFormData =>
Attachment2
-> Owner
-> Repo
-> Id
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     Attachment
     MimeJSON
issueCreateIssueCommentAttachment (Attachment2 FilePath
attachment) (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
"/issues/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets"]
    GiteaRequest
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     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)
    GiteaRequest
  IssueCreateIssueCommentAttachment
  MimeMultipartFormData
  Attachment
  MimeJSON
-> Part
-> GiteaRequest
     IssueCreateIssueCommentAttachment
     MimeMultipartFormData
     Attachment
     MimeJSON
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
attachment

data IssueCreateIssueCommentAttachment  

-- | /Optional Param/ "name" - name of the attachment
instance HasOptionalParam IssueCreateIssueCommentAttachment Name where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest
  IssueCreateIssueCommentAttachment contentType res accept
-> Name
-> GiteaRequest
     IssueCreateIssueCommentAttachment contentType res accept
applyOptionalParam GiteaRequest
  IssueCreateIssueCommentAttachment contentType res accept
req (Name Text
xs) =
    GiteaRequest
  IssueCreateIssueCommentAttachment contentType res accept
req GiteaRequest
  IssueCreateIssueCommentAttachment contentType res accept
-> [QueryItem]
-> GiteaRequest
     IssueCreateIssueCommentAttachment 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)

-- | @multipart/form-data@
instance Consumes IssueCreateIssueCommentAttachment MimeMultipartFormData

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


-- *** issueCreateIssueDependencies

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/dependencies@
-- 
-- Make the issue in the url depend on the issue in the form.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateIssueDependencies
  :: (Consumes IssueCreateIssueDependencies contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueCreateIssueDependencies contentType Issue MimeJSON
issueCreateIssueDependencies :: forall contentType.
Consumes IssueCreateIssueDependencies contentType =>
ContentType contentType
-> Owner
-> Repo
-> IndexText
-> GiteaRequest
     IssueCreateIssueDependencies contentType Issue MimeJSON
issueCreateIssueDependencies ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueCreateIssueDependencies contentType Issue 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
"/issues/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/dependencies"]
    GiteaRequest
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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
  IssueCreateIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueCreateIssueDependencies contentType 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 IssueCreateIssueDependencies 
instance HasBodyParam IssueCreateIssueDependencies IssueMeta 

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

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


-- *** issueCreateLabel

-- | @POST \/repos\/{owner}\/{repo}\/labels@
-- 
-- Create a label
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateLabel
  :: (Consumes IssueCreateLabel MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueCreateLabel MimeJSON Label MimeJSON
issueCreateLabel :: Consumes IssueCreateLabel MimeJSON =>
Owner
-> Repo -> GiteaRequest IssueCreateLabel MimeJSON Label MimeJSON
issueCreateLabel (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest IssueCreateLabel MimeJSON Label 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
"/labels"]
    GiteaRequest IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueCreateLabel MimeJSON Label 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 IssueCreateLabel 
instance HasBodyParam IssueCreateLabel CreateLabelOption 

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

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


-- *** issueCreateMilestone

-- | @POST \/repos\/{owner}\/{repo}\/milestones@
-- 
-- Create a milestone
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueCreateMilestone
  :: (Consumes IssueCreateMilestone MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueCreateMilestone MimeJSON Milestone MimeJSON
issueCreateMilestone :: Consumes IssueCreateMilestone MimeJSON =>
Owner
-> Repo
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone MimeJSON
issueCreateMilestone (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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
"/milestones"]
    GiteaRequest IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueCreateMilestone MimeJSON Milestone 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 IssueCreateMilestone 
instance HasBodyParam IssueCreateMilestone CreateMilestoneOption 

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

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


-- *** issueDelete

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}@
-- 
-- Delete an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDelete
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of issue to delete
  -> GiteaRequest IssueDelete MimeNoContent NoContent MimeNoContent
issueDelete :: Owner
-> Repo
-> Index
-> GiteaRequest IssueDelete MimeNoContent NoContent MimeNoContent
issueDelete (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueDelete 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
    GiteaRequest IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueDelete 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 IssueDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueDelete 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 IssueDelete  
instance Produces IssueDelete MimeNoContent


-- *** issueDeleteComment

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


-- *** issueDeleteCommentDeprecated

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/comments\/{id}@
-- 
-- Delete a comment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteCommentDeprecated
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexInt -- ^ "index" -  this parameter is ignored
  -> Id -- ^ "id" -  id of comment to delete
  -> GiteaRequest IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
issueDeleteCommentDeprecated :: Owner
-> Repo
-> IndexInt
-> Id
-> GiteaRequest
     IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
issueDeleteCommentDeprecated (Owner Text
owner) (Repo Text
repo) (IndexInt Int
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
"/issues/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
index,ByteString
"/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteCommentDeprecated 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
  IssueDeleteCommentDeprecated MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteCommentDeprecated 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)

{-# DEPRECATED issueDeleteCommentDeprecated "" #-}

data IssueDeleteCommentDeprecated  
instance Produces IssueDeleteCommentDeprecated MimeNoContent


-- *** issueDeleteCommentReaction

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/reactions@
-- 
-- Remove a reaction from a comment of an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteCommentReaction
  :: (Consumes IssueDeleteCommentReaction MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment to edit
  -> GiteaRequest IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
issueDeleteCommentReaction :: Consumes IssueDeleteCommentReaction MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest
     IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
issueDeleteCommentReaction (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteCommentReaction MimeJSON 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
"/issues/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/reactions"]
    GiteaRequest
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteCommentReaction 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
  IssueDeleteCommentReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteCommentReaction 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 IssueDeleteCommentReaction 
instance HasBodyParam IssueDeleteCommentReaction EditReactionOption 

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

instance Produces IssueDeleteCommentReaction MimeNoContent


-- *** issueDeleteIssueAttachment

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/assets\/{attachment_id}@
-- 
-- Delete an issue attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteIssueAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to delete
  -> GiteaRequest IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
issueDeleteIssueAttachment :: Owner
-> Repo
-> Index
-> AttachmentId
-> GiteaRequest
     IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
issueDeleteIssueAttachment (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteIssueAttachment 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteIssueAttachment 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
  IssueDeleteIssueAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteIssueAttachment 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 IssueDeleteIssueAttachment  
instance Produces IssueDeleteIssueAttachment MimeNoContent


-- *** issueDeleteIssueCommentAttachment

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/assets\/{attachment_id}@
-- 
-- Delete a comment attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteIssueCommentAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to delete
  -> GiteaRequest IssueDeleteIssueCommentAttachment MimeNoContent NoContent MimeNoContent
issueDeleteIssueCommentAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     MimeNoContent
     NoContent
     MimeNoContent
issueDeleteIssueCommentAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
"/issues/comments/",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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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
  IssueDeleteIssueCommentAttachment
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteIssueCommentAttachment
     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 IssueDeleteIssueCommentAttachment  
instance Produces IssueDeleteIssueCommentAttachment MimeNoContent


-- *** issueDeleteIssueReaction

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/reactions@
-- 
-- Remove a reaction from an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteIssueReaction
  :: (Consumes IssueDeleteIssueReaction MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
issueDeleteIssueReaction :: Consumes IssueDeleteIssueReaction MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest
     IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
issueDeleteIssueReaction (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteIssueReaction MimeJSON 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reactions"]
    GiteaRequest
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteIssueReaction 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
  IssueDeleteIssueReaction MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteIssueReaction 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 IssueDeleteIssueReaction 
instance HasBodyParam IssueDeleteIssueReaction EditReactionOption 

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

instance Produces IssueDeleteIssueReaction MimeNoContent


-- *** issueDeleteLabel

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


-- *** issueDeleteMilestone

-- | @DELETE \/repos\/{owner}\/{repo}\/milestones\/{id}@
-- 
-- Delete a milestone
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteMilestone
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  the milestone to delete, identified by ID and if not available by name
  -> GiteaRequest IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
issueDeleteMilestone :: Owner
-> Repo
-> IdText
-> GiteaRequest
     IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
issueDeleteMilestone (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteMilestone 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
"/milestones/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteMilestone 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
  IssueDeleteMilestone MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteMilestone 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 IssueDeleteMilestone  
instance Produces IssueDeleteMilestone MimeNoContent


-- *** issueDeleteStopWatch

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/stopwatch\/delete@
-- 
-- Delete an issue's existing stopwatch.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteStopWatch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to stop the stopwatch on
  -> GiteaRequest IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
issueDeleteStopWatch :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
issueDeleteStopWatch (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteStopWatch 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/stopwatch/delete"]
    GiteaRequest
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteStopWatch 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
  IssueDeleteStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteStopWatch 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 IssueDeleteStopWatch  
instance Produces IssueDeleteStopWatch MimeNoContent


-- *** issueDeleteSubscription

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/subscriptions\/{user}@
-- 
-- Unsubscribe user from issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteSubscription
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> User2 -- ^ "user" -  user witch unsubscribe
  -> GiteaRequest IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
issueDeleteSubscription :: Owner
-> Repo
-> Index
-> User2
-> GiteaRequest
     IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
issueDeleteSubscription (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (User2 Text
user) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteSubscription 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/subscriptions/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
user]
    GiteaRequest
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteSubscription 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
  IssueDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteSubscription 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 IssueDeleteSubscription  
instance Produces IssueDeleteSubscription MimeNoContent


-- *** issueDeleteTime

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/times\/{id}@
-- 
-- Delete specific tracked time
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueDeleteTime
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> Id -- ^ "id" -  id of time to delete
  -> GiteaRequest IssueDeleteTime MimeNoContent NoContent MimeNoContent
issueDeleteTime :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     IssueDeleteTime MimeNoContent NoContent MimeNoContent
issueDeleteTime (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueDeleteTime 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/times/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueDeleteTime 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 IssueDeleteTime  
instance Produces IssueDeleteTime MimeNoContent


-- *** issueEditComment

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/comments\/{id}@
-- 
-- Edit a comment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditComment
  :: (Consumes IssueEditComment MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment to edit
  -> GiteaRequest IssueEditComment MimeJSON Comment MimeJSON
issueEditComment :: Consumes IssueEditComment MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest IssueEditComment MimeJSON Comment MimeJSON
issueEditComment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueEditComment MimeJSON Comment 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
"/issues/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueEditComment MimeJSON Comment 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 IssueEditComment 
instance HasBodyParam IssueEditComment EditIssueCommentOption 

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

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


-- *** issueEditCommentDeprecated

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/{index}\/comments\/{id}@
-- 
-- Edit a comment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditCommentDeprecated
  :: (Consumes IssueEditCommentDeprecated MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexInt -- ^ "index" -  this parameter is ignored
  -> Id -- ^ "id" -  id of the comment to edit
  -> GiteaRequest IssueEditCommentDeprecated MimeJSON Comment MimeJSON
issueEditCommentDeprecated :: Consumes IssueEditCommentDeprecated MimeJSON =>
Owner
-> Repo
-> IndexInt
-> Id
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment MimeJSON
issueEditCommentDeprecated (Owner Text
owner) (Repo Text
repo) (IndexInt Int
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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
"/issues/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
index,ByteString
"/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 IssueEditCommentDeprecated MimeJSON Comment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueEditCommentDeprecated MimeJSON Comment 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 issueEditCommentDeprecated "" #-}

data IssueEditCommentDeprecated 
instance HasBodyParam IssueEditCommentDeprecated EditIssueCommentOption 

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

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


-- *** issueEditIssue

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/{index}@
-- 
-- Edit an issue. If using deadline only the date will be taken into account, and time of day ignored.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditIssue
  :: (Consumes IssueEditIssue MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to edit
  -> GiteaRequest IssueEditIssue MimeJSON Issue MimeJSON
issueEditIssue :: Consumes IssueEditIssue MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssueEditIssue MimeJSON Issue MimeJSON
issueEditIssue (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueEditIssue MimeJSON Issue 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
    GiteaRequest IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue MimeJSON Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueEditIssue MimeJSON 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 IssueEditIssue 
instance HasBodyParam IssueEditIssue EditIssueOption 

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

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


-- *** issueEditIssueAttachment

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/{index}\/assets\/{attachment_id}@
-- 
-- Edit an issue attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditIssueAttachment
  :: (Consumes IssueEditIssueAttachment MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to edit
  -> GiteaRequest IssueEditIssueAttachment MimeJSON Attachment MimeJSON
issueEditIssueAttachment :: Consumes IssueEditIssueAttachment MimeJSON =>
Owner
-> Repo
-> Index
-> AttachmentId
-> GiteaRequest
     IssueEditIssueAttachment MimeJSON Attachment MimeJSON
issueEditIssueAttachment (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueEditIssueAttachment 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueEditIssueAttachment 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 IssueEditIssueAttachment 
instance HasBodyParam IssueEditIssueAttachment EditAttachmentOptions 

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

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


-- *** issueEditIssueCommentAttachment

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/assets\/{attachment_id}@
-- 
-- Edit a comment attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditIssueCommentAttachment
  :: (Consumes IssueEditIssueCommentAttachment MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to edit
  -> GiteaRequest IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
issueEditIssueCommentAttachment :: Consumes IssueEditIssueCommentAttachment MimeJSON =>
Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
issueEditIssueCommentAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
"/issues/comments/",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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueEditIssueCommentAttachment 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
  IssueEditIssueCommentAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueEditIssueCommentAttachment 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 IssueEditIssueCommentAttachment 
instance HasBodyParam IssueEditIssueCommentAttachment EditAttachmentOptions 

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

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


-- *** issueEditIssueDeadline

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/deadline@
-- 
-- Set an issue deadline. If set to null, the deadline is deleted. If using deadline only the date will be taken into account, and time of day ignored.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditIssueDeadline
  :: (Consumes IssueEditIssueDeadline MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to create or update a deadline on
  -> GiteaRequest IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
issueEditIssueDeadline :: Consumes IssueEditIssueDeadline MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
issueEditIssueDeadline (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/deadline"]
    GiteaRequest IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline MimeJSON IssueDeadline MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueEditIssueDeadline MimeJSON IssueDeadline 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 IssueEditIssueDeadline 
instance HasBodyParam IssueEditIssueDeadline EditDeadlineOption 

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

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


-- *** issueEditLabel

-- | @PATCH \/repos\/{owner}\/{repo}\/labels\/{id}@
-- 
-- Update a label
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditLabel
  :: (Consumes IssueEditLabel MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the label to edit
  -> GiteaRequest IssueEditLabel MimeJSON Label MimeJSON
issueEditLabel :: Consumes IssueEditLabel MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest IssueEditLabel MimeJSON Label MimeJSON
issueEditLabel (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueEditLabel MimeJSON Label 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
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueEditLabel MimeJSON Label 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 IssueEditLabel 
instance HasBodyParam IssueEditLabel EditLabelOption 

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

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


-- *** issueEditMilestone

-- | @PATCH \/repos\/{owner}\/{repo}\/milestones\/{id}@
-- 
-- Update a milestone
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueEditMilestone
  :: (Consumes IssueEditMilestone MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  the milestone to edit, identified by ID and if not available by name
  -> GiteaRequest IssueEditMilestone MimeJSON Milestone MimeJSON
issueEditMilestone :: Consumes IssueEditMilestone MimeJSON =>
Owner
-> Repo
-> IdText
-> GiteaRequest IssueEditMilestone MimeJSON Milestone MimeJSON
issueEditMilestone (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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
"/milestones/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone MimeJSON Milestone MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueEditMilestone MimeJSON Milestone 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 IssueEditMilestone 
instance HasBodyParam IssueEditMilestone EditMilestoneOption 

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

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


-- *** issueGetComment

-- | @GET \/repos\/{owner}\/{repo}\/issues\/comments\/{id}@
-- 
-- Get a comment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetComment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment
  -> GiteaRequest IssueGetComment MimeNoContent Comment MimeJSON
issueGetComment :: Owner
-> Repo
-> Id
-> GiteaRequest IssueGetComment MimeNoContent Comment MimeJSON
issueGetComment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetComment MimeNoContent Comment 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/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment MimeNoContent Comment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetComment MimeNoContent Comment 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 IssueGetComment  
-- | @application/json@
instance Produces IssueGetComment MimeJSON


-- *** issueGetCommentReactions

-- | @GET \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/reactions@
-- 
-- Get a list of reactions from a comment of an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetCommentReactions
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment to edit
  -> GiteaRequest IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
issueGetCommentReactions :: Owner
-> Repo
-> Id
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
issueGetCommentReactions (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/reactions"]
    GiteaRequest
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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
  IssueGetCommentReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetCommentReactions MimeNoContent [Reaction] 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 IssueGetCommentReactions  
-- | @application/json@
instance Produces IssueGetCommentReactions MimeJSON


-- *** issueGetComments

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/comments@
-- 
-- List all comments on an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetComments
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueGetComments MimeNoContent [Comment] MimeJSON
issueGetComments :: Owner
-> Repo
-> Index
-> GiteaRequest IssueGetComments MimeNoContent [Comment] MimeJSON
issueGetComments (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/comments"]
    GiteaRequest IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetComments MimeNoContent [Comment] 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 IssueGetComments  

-- | /Optional Param/ "since" - if provided, only comments updated since the specified time are returned.
instance HasOptionalParam IssueGetComments Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetComments contentType res accept
-> Since -> GiteaRequest IssueGetComments contentType res accept
applyOptionalParam GiteaRequest IssueGetComments contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueGetComments contentType res accept
req GiteaRequest IssueGetComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetComments 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" - if provided, only comments updated before the provided time are returned.
instance HasOptionalParam IssueGetComments Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetComments contentType res accept
-> Before -> GiteaRequest IssueGetComments contentType res accept
applyOptionalParam GiteaRequest IssueGetComments contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueGetComments contentType res accept
req GiteaRequest IssueGetComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetComments 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)
-- | @application/json@
instance Produces IssueGetComments MimeJSON


-- *** issueGetCommentsAndTimeline

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/timeline@
-- 
-- List all comments and events on an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetCommentsAndTimeline
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueGetCommentsAndTimeline MimeNoContent [TimelineComment] MimeJSON
issueGetCommentsAndTimeline :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     MimeJSON
issueGetCommentsAndTimeline (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/timeline"]
    GiteaRequest
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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
  IssueGetCommentsAndTimeline
  MimeNoContent
  [TimelineComment]
  MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetCommentsAndTimeline
     MimeNoContent
     [TimelineComment]
     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 IssueGetCommentsAndTimeline  

-- | /Optional Param/ "since" - if provided, only comments updated since the specified time are returned.
instance HasOptionalParam IssueGetCommentsAndTimeline Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> Since
-> GiteaRequest IssueGetCommentsAndTimeline contentType res accept
applyOptionalParam GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetCommentsAndTimeline 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/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueGetCommentsAndTimeline Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> Page
-> GiteaRequest IssueGetCommentsAndTimeline contentType res accept
applyOptionalParam GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetCommentsAndTimeline 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 IssueGetCommentsAndTimeline Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> Limit
-> GiteaRequest IssueGetCommentsAndTimeline contentType res accept
applyOptionalParam GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetCommentsAndTimeline 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/ "before" - if provided, only comments updated before the provided time are returned.
instance HasOptionalParam IssueGetCommentsAndTimeline Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> Before
-> GiteaRequest IssueGetCommentsAndTimeline contentType res accept
applyOptionalParam GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueGetCommentsAndTimeline contentType res accept
req GiteaRequest IssueGetCommentsAndTimeline contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetCommentsAndTimeline 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)
-- | @application/json@
instance Produces IssueGetCommentsAndTimeline MimeJSON


-- *** issueGetIssue

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}@
-- 
-- Get an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetIssue
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to get
  -> GiteaRequest IssueGetIssue MimeNoContent Issue MimeJSON
issueGetIssue :: Owner
-> Repo
-> Index
-> GiteaRequest IssueGetIssue MimeNoContent Issue MimeJSON
issueGetIssue (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetIssue 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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
    GiteaRequest IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetIssue 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 IssueGetIssue MimeNoContent Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetIssue 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 IssueGetIssue  
-- | @application/json@
instance Produces IssueGetIssue MimeJSON


-- *** issueGetIssueAttachment

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/assets\/{attachment_id}@
-- 
-- Get an issue attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetIssueAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to get
  -> GiteaRequest IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
issueGetIssueAttachment :: Owner
-> Repo
-> Index
-> AttachmentId
-> GiteaRequest
     IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
issueGetIssueAttachment (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetIssueAttachment 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
    GiteaRequest
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetIssueAttachment 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
  IssueGetIssueAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetIssueAttachment 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 IssueGetIssueAttachment  
-- | @application/json@
instance Produces IssueGetIssueAttachment MimeJSON


-- *** issueGetIssueCommentAttachment

-- | @GET \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/assets\/{attachment_id}@
-- 
-- Get a comment attachment
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetIssueCommentAttachment
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment
  -> AttachmentId -- ^ "attachmentId" -  id of the attachment to get
  -> GiteaRequest IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
issueGetIssueCommentAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
     IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
issueGetIssueCommentAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
"/issues/comments/",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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetIssueCommentAttachment 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
  IssueGetIssueCommentAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetIssueCommentAttachment 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 IssueGetIssueCommentAttachment  
-- | @application/json@
instance Produces IssueGetIssueCommentAttachment MimeJSON


-- *** issueGetIssueReactions

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/reactions@
-- 
-- Get a list reactions of an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetIssueReactions
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
issueGetIssueReactions :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
issueGetIssueReactions (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reactions"]
    GiteaRequest
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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
  IssueGetIssueReactions MimeNoContent [Reaction] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetIssueReactions MimeNoContent [Reaction] 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 IssueGetIssueReactions  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueGetIssueReactions Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetIssueReactions contentType res accept
-> Page
-> GiteaRequest IssueGetIssueReactions contentType res accept
applyOptionalParam GiteaRequest IssueGetIssueReactions contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueGetIssueReactions contentType res accept
req GiteaRequest IssueGetIssueReactions contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetIssueReactions 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 IssueGetIssueReactions Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetIssueReactions contentType res accept
-> Limit
-> GiteaRequest IssueGetIssueReactions contentType res accept
applyOptionalParam GiteaRequest IssueGetIssueReactions contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueGetIssueReactions contentType res accept
req GiteaRequest IssueGetIssueReactions contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetIssueReactions 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 IssueGetIssueReactions MimeJSON


-- *** issueGetLabel

-- | @GET \/repos\/{owner}\/{repo}\/labels\/{id}@
-- 
-- Get a single label
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetLabel
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the label to get
  -> GiteaRequest IssueGetLabel MimeNoContent Label MimeJSON
issueGetLabel :: Owner
-> Repo
-> Id
-> GiteaRequest IssueGetLabel MimeNoContent Label MimeJSON
issueGetLabel (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetLabel MimeNoContent Label 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
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetLabel MimeNoContent Label 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 IssueGetLabel  
-- | @application/json@
instance Produces IssueGetLabel MimeJSON


-- *** issueGetLabels

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/labels@
-- 
-- Get an issue's labels
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetLabels
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueGetLabels MimeNoContent [Label] MimeJSON
issueGetLabels :: Owner
-> Repo
-> Index
-> GiteaRequest IssueGetLabels MimeNoContent [Label] MimeJSON
issueGetLabels (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/labels"]
    GiteaRequest IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetLabels MimeNoContent [Label] 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 IssueGetLabels  
-- | @application/json@
instance Produces IssueGetLabels MimeJSON


-- *** issueGetMilestone

-- | @GET \/repos\/{owner}\/{repo}\/milestones\/{id}@
-- 
-- Get a milestone
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetMilestone
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IdText -- ^ "id" -  the milestone to get, identified by ID and if not available by name
  -> GiteaRequest IssueGetMilestone MimeNoContent Milestone MimeJSON
issueGetMilestone :: Owner
-> Repo
-> IdText
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone MimeJSON
issueGetMilestone (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
  Method
-> [ByteString]
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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
"/milestones/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    GiteaRequest IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone MimeNoContent Milestone MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueGetMilestone MimeNoContent Milestone 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 IssueGetMilestone  
-- | @application/json@
instance Produces IssueGetMilestone MimeJSON


-- *** issueGetMilestonesList

-- | @GET \/repos\/{owner}\/{repo}\/milestones@
-- 
-- Get all of a repository's opened milestones
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetMilestonesList
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
issueGetMilestonesList :: Owner
-> Repo
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
issueGetMilestonesList (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
"/milestones"]
    GiteaRequest
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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
  IssueGetMilestonesList MimeNoContent [Milestone] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetMilestonesList MimeNoContent [Milestone] 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 IssueGetMilestonesList  

-- | /Optional Param/ "state" - Milestone state, Recognized values are open, closed and all. Defaults to \"open\"
instance HasOptionalParam IssueGetMilestonesList StateText where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetMilestonesList contentType res accept
-> StateText
-> GiteaRequest IssueGetMilestonesList contentType res accept
applyOptionalParam GiteaRequest IssueGetMilestonesList contentType res accept
req (StateText Text
xs) =
    GiteaRequest IssueGetMilestonesList contentType res accept
req GiteaRequest IssueGetMilestonesList contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetMilestonesList 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
"state", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "name" - filter by milestone name
instance HasOptionalParam IssueGetMilestonesList Name where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetMilestonesList contentType res accept
-> Name
-> GiteaRequest IssueGetMilestonesList contentType res accept
applyOptionalParam GiteaRequest IssueGetMilestonesList contentType res accept
req (Name Text
xs) =
    GiteaRequest IssueGetMilestonesList contentType res accept
req GiteaRequest IssueGetMilestonesList contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetMilestonesList 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)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueGetMilestonesList Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetMilestonesList contentType res accept
-> Page
-> GiteaRequest IssueGetMilestonesList contentType res accept
applyOptionalParam GiteaRequest IssueGetMilestonesList contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueGetMilestonesList contentType res accept
req GiteaRequest IssueGetMilestonesList contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetMilestonesList 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 IssueGetMilestonesList Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetMilestonesList contentType res accept
-> Limit
-> GiteaRequest IssueGetMilestonesList contentType res accept
applyOptionalParam GiteaRequest IssueGetMilestonesList contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueGetMilestonesList contentType res accept
req GiteaRequest IssueGetMilestonesList contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetMilestonesList 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 IssueGetMilestonesList MimeJSON


-- *** issueGetRepoComments

-- | @GET \/repos\/{owner}\/{repo}\/issues\/comments@
-- 
-- List all comments in a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueGetRepoComments
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueGetRepoComments MimeNoContent [Comment] MimeJSON
issueGetRepoComments :: Owner
-> Repo
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] MimeJSON
issueGetRepoComments (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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/comments"]
    GiteaRequest IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments MimeNoContent [Comment] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueGetRepoComments MimeNoContent [Comment] 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 IssueGetRepoComments  

-- | /Optional Param/ "since" - if provided, only comments updated since the provided time are returned.
instance HasOptionalParam IssueGetRepoComments Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetRepoComments contentType res accept
-> Since
-> GiteaRequest IssueGetRepoComments contentType res accept
applyOptionalParam GiteaRequest IssueGetRepoComments contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueGetRepoComments contentType res accept
req GiteaRequest IssueGetRepoComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetRepoComments 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" - if provided, only comments updated before the provided time are returned.
instance HasOptionalParam IssueGetRepoComments Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetRepoComments contentType res accept
-> Before
-> GiteaRequest IssueGetRepoComments contentType res accept
applyOptionalParam GiteaRequest IssueGetRepoComments contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueGetRepoComments contentType res accept
req GiteaRequest IssueGetRepoComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetRepoComments 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 IssueGetRepoComments Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetRepoComments contentType res accept
-> Page -> GiteaRequest IssueGetRepoComments contentType res accept
applyOptionalParam GiteaRequest IssueGetRepoComments contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueGetRepoComments contentType res accept
req GiteaRequest IssueGetRepoComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetRepoComments 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 IssueGetRepoComments Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueGetRepoComments contentType res accept
-> Limit
-> GiteaRequest IssueGetRepoComments contentType res accept
applyOptionalParam GiteaRequest IssueGetRepoComments contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueGetRepoComments contentType res accept
req GiteaRequest IssueGetRepoComments contentType res accept
-> [QueryItem]
-> GiteaRequest IssueGetRepoComments 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 IssueGetRepoComments MimeJSON


-- *** issueListBlocks

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/blocks@
-- 
-- List issues that are blocked by this issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueListBlocks
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueListBlocks MimeNoContent [Issue] MimeJSON
issueListBlocks :: Owner
-> Repo
-> IndexText
-> GiteaRequest IssueListBlocks MimeNoContent [Issue] MimeJSON
issueListBlocks (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueListBlocks 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/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/blocks"]
    GiteaRequest IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueListBlocks 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 IssueListBlocks  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueListBlocks Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListBlocks contentType res accept
-> Page -> GiteaRequest IssueListBlocks contentType res accept
applyOptionalParam GiteaRequest IssueListBlocks contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueListBlocks contentType res accept
req GiteaRequest IssueListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListBlocks 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 IssueListBlocks Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListBlocks contentType res accept
-> Limit -> GiteaRequest IssueListBlocks contentType res accept
applyOptionalParam GiteaRequest IssueListBlocks contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueListBlocks contentType res accept
req GiteaRequest IssueListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListBlocks 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 IssueListBlocks MimeJSON


-- *** issueListIssueAttachments

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/assets@
-- 
-- List issue's attachments
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueListIssueAttachments
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
issueListIssueAttachments :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
issueListIssueAttachments (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueListIssueAttachments 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/assets"]
    GiteaRequest
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueListIssueAttachments 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
  IssueListIssueAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueListIssueAttachments 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 IssueListIssueAttachments  
-- | @application/json@
instance Produces IssueListIssueAttachments MimeJSON


-- *** issueListIssueCommentAttachments

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


-- *** issueListIssueDependencies

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/dependencies@
-- 
-- List an issue's dependencies, i.e all issues that block this issue.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueListIssueDependencies
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
issueListIssueDependencies :: Owner
-> Repo
-> IndexText
-> GiteaRequest
     IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
issueListIssueDependencies (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueListIssueDependencies 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/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/dependencies"]
    GiteaRequest
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueListIssueDependencies 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
  IssueListIssueDependencies MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueListIssueDependencies 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 IssueListIssueDependencies  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueListIssueDependencies Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssueDependencies contentType res accept
-> Page
-> GiteaRequest IssueListIssueDependencies contentType res accept
applyOptionalParam GiteaRequest IssueListIssueDependencies contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueListIssueDependencies contentType res accept
req GiteaRequest IssueListIssueDependencies contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssueDependencies 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 IssueListIssueDependencies Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssueDependencies contentType res accept
-> Limit
-> GiteaRequest IssueListIssueDependencies contentType res accept
applyOptionalParam GiteaRequest IssueListIssueDependencies contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueListIssueDependencies contentType res accept
req GiteaRequest IssueListIssueDependencies contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssueDependencies 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 IssueListIssueDependencies MimeJSON


-- *** issueListIssues

-- | @GET \/repos\/{owner}\/{repo}\/issues@
-- 
-- List a repository's issues
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueListIssues
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueListIssues MimeNoContent [Issue] MimeJSON
issueListIssues :: Owner
-> Repo
-> GiteaRequest IssueListIssues MimeNoContent [Issue] MimeJSON
issueListIssues (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest IssueListIssues 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"]
    GiteaRequest IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueListIssues 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 IssueListIssues  

-- | /Optional Param/ "state" - whether issue is open or closed
instance HasOptionalParam IssueListIssues State3 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> State3 -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (State3 E'State4
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State4) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State4 -> Maybe E'State4
forall a. a -> Maybe a
Just E'State4
xs)

-- | /Optional Param/ "labels" - comma separated list of labels. Fetch only issues that have any of this labels. Non existent labels are discarded
instance HasOptionalParam IssueListIssues Labels where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Labels -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Labels Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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
"labels", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "q" - search string
instance HasOptionalParam IssueListIssues Q where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Q -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Q Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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/ "type" - filter by type (issues / pulls) if set
instance HasOptionalParam IssueListIssues ParamType2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> ParamType2
-> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (ParamType2 E'Type3
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Type3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"type", E'Type3 -> Maybe E'Type3
forall a. a -> Maybe a
Just E'Type3
xs)

-- | /Optional Param/ "milestones" - comma separated list of milestone names or ids. It uses names and fall back to ids. Fetch only issues that have any of this milestones. Non existent milestones are discarded
instance HasOptionalParam IssueListIssues Milestones where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Milestones
-> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Milestones Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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
"milestones", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "since" - Only show items updated after the given time. This is a timestamp in RFC 3339 format
instance HasOptionalParam IssueListIssues Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Since -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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 items updated before the given time. This is a timestamp in RFC 3339 format
instance HasOptionalParam IssueListIssues Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Before -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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/ "created_by" - Only show items which were created by the given user
instance HasOptionalParam IssueListIssues CreatedBy where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> CreatedBy -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (CreatedBy Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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
"created_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "assigned_by" - Only show items for which the given user is assigned
instance HasOptionalParam IssueListIssues AssignedBy where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> AssignedBy
-> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (AssignedBy Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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
"assigned_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "mentioned_by" - Only show items in which the given user was mentioned
instance HasOptionalParam IssueListIssues MentionedBy where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> MentionedBy
-> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (MentionedBy Text
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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
"mentioned_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueListIssues Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Page -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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 IssueListIssues Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListIssues contentType res accept
-> Limit -> GiteaRequest IssueListIssues contentType res accept
applyOptionalParam GiteaRequest IssueListIssues contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueListIssues contentType res accept
req GiteaRequest IssueListIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListIssues 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 IssueListIssues MimeJSON


-- *** issueListLabels

-- | @GET \/repos\/{owner}\/{repo}\/labels@
-- 
-- Get all of a repository's labels
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueListLabels
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest IssueListLabels MimeNoContent [Label] MimeJSON
issueListLabels :: Owner
-> Repo
-> GiteaRequest IssueListLabels MimeNoContent [Label] MimeJSON
issueListLabels (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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
"/labels"]
    GiteaRequest IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueListLabels MimeNoContent [Label] 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 IssueListLabels  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueListLabels Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListLabels contentType res accept
-> Page -> GiteaRequest IssueListLabels contentType res accept
applyOptionalParam GiteaRequest IssueListLabels contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueListLabels contentType res accept
req GiteaRequest IssueListLabels contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListLabels 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 IssueListLabels Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueListLabels contentType res accept
-> Limit -> GiteaRequest IssueListLabels contentType res accept
applyOptionalParam GiteaRequest IssueListLabels contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueListLabels contentType res accept
req GiteaRequest IssueListLabels contentType res accept
-> [QueryItem]
-> GiteaRequest IssueListLabels 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 IssueListLabels MimeJSON


-- *** issuePostCommentReaction

-- | @POST \/repos\/{owner}\/{repo}\/issues\/comments\/{id}\/reactions@
-- 
-- Add a reaction to a comment of an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issuePostCommentReaction
  :: (Consumes IssuePostCommentReaction MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Id -- ^ "id" -  id of the comment to edit
  -> GiteaRequest IssuePostCommentReaction MimeJSON Reaction MimeJSON
issuePostCommentReaction :: Consumes IssuePostCommentReaction MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction MimeJSON
issuePostCommentReaction (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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
"/issues/comments/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/reactions"]
    GiteaRequest IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssuePostCommentReaction MimeJSON Reaction 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 IssuePostCommentReaction 
instance HasBodyParam IssuePostCommentReaction EditReactionOption 

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

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


-- *** issuePostIssueReaction

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/reactions@
-- 
-- Add a reaction to an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issuePostIssueReaction
  :: (Consumes IssuePostIssueReaction MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssuePostIssueReaction MimeJSON Reaction MimeJSON
issuePostIssueReaction :: Consumes IssuePostIssueReaction MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction MimeJSON
issuePostIssueReaction (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reactions"]
    GiteaRequest IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction MimeJSON Reaction MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssuePostIssueReaction MimeJSON Reaction 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 IssuePostIssueReaction 
instance HasBodyParam IssuePostIssueReaction EditReactionOption 

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

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


-- *** issueRemoveIssueBlocking

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/blocks@
-- 
-- Unblock the issue given in the body by the issue in path
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueRemoveIssueBlocking
  :: (Consumes IssueRemoveIssueBlocking contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueRemoveIssueBlocking contentType Issue MimeJSON
issueRemoveIssueBlocking :: forall contentType.
Consumes IssueRemoveIssueBlocking contentType =>
ContentType contentType
-> Owner
-> Repo
-> IndexText
-> GiteaRequest IssueRemoveIssueBlocking contentType Issue MimeJSON
issueRemoveIssueBlocking ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueRemoveIssueBlocking contentType Issue 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
"/issues/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/blocks"]
    GiteaRequest IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking contentType Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueRemoveIssueBlocking contentType 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 IssueRemoveIssueBlocking 
instance HasBodyParam IssueRemoveIssueBlocking IssueMeta 

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

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


-- *** issueRemoveIssueDependencies

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/dependencies@
-- 
-- Remove an issue dependency
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueRemoveIssueDependencies
  :: (Consumes IssueRemoveIssueDependencies contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> IndexText -- ^ "index" -  index of the issue
  -> GiteaRequest IssueRemoveIssueDependencies contentType Issue MimeJSON
issueRemoveIssueDependencies :: forall contentType.
Consumes IssueRemoveIssueDependencies contentType =>
ContentType contentType
-> Owner
-> Repo
-> IndexText
-> GiteaRequest
     IssueRemoveIssueDependencies contentType Issue MimeJSON
issueRemoveIssueDependencies ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IndexText Text
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueRemoveIssueDependencies contentType Issue 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
"/issues/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
index,ByteString
"/dependencies"]
    GiteaRequest
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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
  IssueRemoveIssueDependencies contentType Issue MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueRemoveIssueDependencies contentType 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 IssueRemoveIssueDependencies 
instance HasBodyParam IssueRemoveIssueDependencies IssueMeta 

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

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


-- *** issueRemoveLabel

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/labels\/{id}@
-- 
-- Remove a label from an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueRemoveLabel
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> Id -- ^ "id" -  id of the label to remove
  -> GiteaRequest IssueRemoveLabel MimeNoContent NoContent MimeNoContent
issueRemoveLabel :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
     IssueRemoveLabel MimeNoContent NoContent MimeNoContent
issueRemoveLabel (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueRemoveLabel 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueRemoveLabel 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 IssueRemoveLabel  
instance Produces IssueRemoveLabel MimeNoContent


-- *** issueReplaceLabels

-- | @PUT \/repos\/{owner}\/{repo}\/issues\/{index}\/labels@
-- 
-- Replace an issue's labels
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueReplaceLabels
  :: (Consumes IssueReplaceLabels MimeJSON)
  => Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueReplaceLabels MimeJSON [Label] MimeJSON
issueReplaceLabels :: Consumes IssueReplaceLabels MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] MimeJSON
issueReplaceLabels (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/labels"]
    GiteaRequest IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels MimeJSON [Label] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueReplaceLabels MimeJSON [Label] 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 IssueReplaceLabels 
instance HasBodyParam IssueReplaceLabels IssueLabelsOption 

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

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


-- *** issueResetTime

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/times@
-- 
-- Reset a tracked time of an issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueResetTime
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to add tracked time to
  -> GiteaRequest IssueResetTime MimeNoContent NoContent MimeNoContent
issueResetTime :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueResetTime MimeNoContent NoContent MimeNoContent
issueResetTime (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueResetTime 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/times"]
    GiteaRequest IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueResetTime 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 IssueResetTime MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueResetTime 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 IssueResetTime  
instance Produces IssueResetTime MimeNoContent


-- *** issueSearchIssues

-- | @GET \/repos\/issues\/search@
-- 
-- Search for issues across the repositories that the user has access to
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueSearchIssues
  :: GiteaRequest IssueSearchIssues MimeNoContent [Issue] MimeJSON
issueSearchIssues :: GiteaRequest IssueSearchIssues MimeNoContent [Issue] MimeJSON
issueSearchIssues =
  Method
-> [ByteString]
-> GiteaRequest IssueSearchIssues MimeNoContent [Issue] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/issues/search"]
    GiteaRequest IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues  

-- | /Optional Param/ "state" - State of the issue
instance HasOptionalParam IssueSearchIssues State where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> State -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (State E'State2
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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/ "labels" - Comma-separated list of label names. Fetch only issues that have any of these labels. Non existent labels are discarded.
instance HasOptionalParam IssueSearchIssues Labels where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Labels -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Labels Text
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"labels", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "milestones" - Comma-separated list of milestone names. Fetch only issues that have any of these milestones. Non existent milestones are discarded.
instance HasOptionalParam IssueSearchIssues Milestones where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Milestones
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Milestones Text
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"milestones", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "q" - Search string
instance HasOptionalParam IssueSearchIssues Q where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Q -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Q Text
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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/ "priority_repo_id" - Repository ID to prioritize in the results
instance HasOptionalParam IssueSearchIssues PriorityRepoId where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> PriorityRepoId
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (PriorityRepoId Integer
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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_repo_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "type" - Filter by issue type
instance HasOptionalParam IssueSearchIssues ParamType2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> ParamType2
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (ParamType2 E'Type3
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Type3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"type", E'Type3 -> Maybe E'Type3
forall a. a -> Maybe a
Just E'Type3
xs)

-- | /Optional Param/ "since" - Only show issues updated after the given time (RFC 3339 format)
instance HasOptionalParam IssueSearchIssues Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Since -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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 issues updated before the given time (RFC 3339 format)
instance HasOptionalParam IssueSearchIssues Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Before -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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/ "assigned" - Filter issues or pulls assigned to the authenticated user
instance HasOptionalParam IssueSearchIssues Assigned where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Assigned
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Assigned Bool
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"assigned", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "created" - Filter issues or pulls created by the authenticated user
instance HasOptionalParam IssueSearchIssues Created where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Created -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Created Bool
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"created", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "mentioned" - Filter issues or pulls mentioning the authenticated user
instance HasOptionalParam IssueSearchIssues Mentioned where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Mentioned
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Mentioned Bool
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"mentioned", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "review_requested" - Filter pull requests where the authenticated user's review was requested
instance HasOptionalParam IssueSearchIssues ReviewRequested where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> ReviewRequested
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (ReviewRequested Bool
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"review_requested", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "reviewed" - Filter pull requests reviewed by the authenticated user
instance HasOptionalParam IssueSearchIssues Reviewed where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Reviewed
-> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Reviewed Bool
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"reviewed", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "owner" - Filter by repository owner
instance HasOptionalParam IssueSearchIssues Owner where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Owner -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Owner Text
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"owner", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "team" - Filter by team (requires organization owner parameter)
instance HasOptionalParam IssueSearchIssues Team2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Team2 -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Team2 Text
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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
"team", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "page" - Page number of results to return (1-based)
instance HasOptionalParam IssueSearchIssues Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Page -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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" - Number of items per page
instance HasOptionalParam IssueSearchIssues Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSearchIssues contentType res accept
-> Limit -> GiteaRequest IssueSearchIssues contentType res accept
applyOptionalParam GiteaRequest IssueSearchIssues contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueSearchIssues contentType res accept
req GiteaRequest IssueSearchIssues contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSearchIssues 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 IssueSearchIssues MimeJSON


-- *** issueStartStopWatch

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/stopwatch\/start@
-- 
-- Start stopwatch on an issue.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueStartStopWatch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to create the stopwatch on
  -> GiteaRequest IssueStartStopWatch MimeNoContent NoContent MimeNoContent
issueStartStopWatch :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueStartStopWatch MimeNoContent NoContent MimeNoContent
issueStartStopWatch (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueStartStopWatch 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/stopwatch/start"]
    GiteaRequest
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueStartStopWatch 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
  IssueStartStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueStartStopWatch 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 IssueStartStopWatch  
instance Produces IssueStartStopWatch MimeNoContent


-- *** issueStopStopWatch

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/stopwatch\/stop@
-- 
-- Stop an issue's existing stopwatch.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueStopStopWatch
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue to stop the stopwatch on
  -> GiteaRequest IssueStopStopWatch MimeNoContent NoContent MimeNoContent
issueStopStopWatch :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueStopStopWatch MimeNoContent NoContent MimeNoContent
issueStopStopWatch (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueStopStopWatch 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/stopwatch/stop"]
    GiteaRequest
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueStopStopWatch 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
  IssueStopStopWatch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueStopStopWatch 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 IssueStopStopWatch  
instance Produces IssueStopStopWatch MimeNoContent


-- *** issueSubscriptions

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/subscriptions@
-- 
-- Get users who subscribed on an issue.
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueSubscriptions
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueSubscriptions MimeNoContent [User] MimeJSON
issueSubscriptions :: Owner
-> Repo
-> Index
-> GiteaRequest IssueSubscriptions MimeNoContent [User] MimeJSON
issueSubscriptions (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest IssueSubscriptions 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/subscriptions"]
    GiteaRequest IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions  

-- | /Optional Param/ "page" - page number of results to return (1-based)
instance HasOptionalParam IssueSubscriptions Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSubscriptions contentType res accept
-> Page -> GiteaRequest IssueSubscriptions contentType res accept
applyOptionalParam GiteaRequest IssueSubscriptions contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueSubscriptions contentType res accept
req GiteaRequest IssueSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueSubscriptions contentType res accept
-> Limit -> GiteaRequest IssueSubscriptions contentType res accept
applyOptionalParam GiteaRequest IssueSubscriptions contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueSubscriptions contentType res accept
req GiteaRequest IssueSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest IssueSubscriptions 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 IssueSubscriptions MimeJSON


-- *** issueTrackedTimes

-- | @GET \/repos\/{owner}\/{repo}\/issues\/{index}\/times@
-- 
-- List an issue's tracked times
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
issueTrackedTimes
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of the issue
  -> GiteaRequest IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
issueTrackedTimes :: Owner
-> Repo
-> Index
-> GiteaRequest
     IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
issueTrackedTimes (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest
     IssueTrackedTimes 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/times"]
    GiteaRequest IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     IssueTrackedTimes 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 IssueTrackedTimes  

-- | /Optional Param/ "user" - optional filter by user (available for issue managers)
instance HasOptionalParam IssueTrackedTimes User2 where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueTrackedTimes contentType res accept
-> User2 -> GiteaRequest IssueTrackedTimes contentType res accept
applyOptionalParam GiteaRequest IssueTrackedTimes contentType res accept
req (User2 Text
xs) =
    GiteaRequest IssueTrackedTimes contentType res accept
req GiteaRequest IssueTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest IssueTrackedTimes 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 IssueTrackedTimes Since where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueTrackedTimes contentType res accept
-> Since -> GiteaRequest IssueTrackedTimes contentType res accept
applyOptionalParam GiteaRequest IssueTrackedTimes contentType res accept
req (Since DateTime
xs) =
    GiteaRequest IssueTrackedTimes contentType res accept
req GiteaRequest IssueTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest IssueTrackedTimes 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 IssueTrackedTimes Before where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueTrackedTimes contentType res accept
-> Before -> GiteaRequest IssueTrackedTimes contentType res accept
applyOptionalParam GiteaRequest IssueTrackedTimes contentType res accept
req (Before DateTime
xs) =
    GiteaRequest IssueTrackedTimes contentType res accept
req GiteaRequest IssueTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest IssueTrackedTimes 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 IssueTrackedTimes Page where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueTrackedTimes contentType res accept
-> Page -> GiteaRequest IssueTrackedTimes contentType res accept
applyOptionalParam GiteaRequest IssueTrackedTimes contentType res accept
req (Page Int
xs) =
    GiteaRequest IssueTrackedTimes contentType res accept
req GiteaRequest IssueTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest IssueTrackedTimes 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 IssueTrackedTimes Limit where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest IssueTrackedTimes contentType res accept
-> Limit -> GiteaRequest IssueTrackedTimes contentType res accept
applyOptionalParam GiteaRequest IssueTrackedTimes contentType res accept
req (Limit Int
xs) =
    GiteaRequest IssueTrackedTimes contentType res accept
req GiteaRequest IssueTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest IssueTrackedTimes 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 IssueTrackedTimes MimeJSON


-- *** moveIssuePin

-- | @PATCH \/repos\/{owner}\/{repo}\/issues\/{index}\/pin\/{position}@
-- 
-- Moves the Pin to the given Position
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
moveIssuePin
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of issue
  -> Position -- ^ "position" -  the new position
  -> GiteaRequest MoveIssuePin MimeNoContent NoContent MimeNoContent
moveIssuePin :: Owner
-> Repo
-> Index
-> Position
-> GiteaRequest MoveIssuePin MimeNoContent NoContent MimeNoContent
moveIssuePin (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Position Integer
position) =
  Method
-> [ByteString]
-> GiteaRequest MoveIssuePin MimeNoContent 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/pin/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
position]
    GiteaRequest MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest MoveIssuePin 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 MoveIssuePin MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest MoveIssuePin 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 MoveIssuePin  
instance Produces MoveIssuePin MimeNoContent


-- *** pinIssue

-- | @POST \/repos\/{owner}\/{repo}\/issues\/{index}\/pin@
-- 
-- Pin an Issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
pinIssue
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of issue to pin
  -> GiteaRequest PinIssue MimeNoContent NoContent MimeNoContent
pinIssue :: Owner
-> Repo
-> Index
-> GiteaRequest PinIssue MimeNoContent NoContent MimeNoContent
pinIssue (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest PinIssue 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/pin"]
    GiteaRequest PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest PinIssue 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 PinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest PinIssue 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 PinIssue  
instance Produces PinIssue MimeNoContent


-- *** unpinIssue

-- | @DELETE \/repos\/{owner}\/{repo}\/issues\/{index}\/pin@
-- 
-- Unpin an Issue
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
unpinIssue
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> Index -- ^ "index" -  index of issue to unpin
  -> GiteaRequest UnpinIssue MimeNoContent NoContent MimeNoContent
unpinIssue :: Owner
-> Repo
-> Index
-> GiteaRequest UnpinIssue MimeNoContent NoContent MimeNoContent
unpinIssue (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
  Method
-> [ByteString]
-> GiteaRequest UnpinIssue 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
"/issues/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/pin"]
    GiteaRequest UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UnpinIssue 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 UnpinIssue MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UnpinIssue 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 UnpinIssue  
instance Produces UnpinIssue MimeNoContent