{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}
module Gitea.API.Repository where
import Gitea.Core
import Gitea.MimeTypes
import Gitea.Model as M
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Set as Set
import qualified Data.String as P
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Time as TI
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Media as ME
import qualified Network.HTTP.Types as NH
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH
import Data.Text (Text)
import GHC.Base ((<|>))
import Prelude ((==),(/=),($), (.),(<$>),(<*>),(>>=),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P
acceptRepoTransfer
:: Owner
-> Repo
-> GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
acceptRepoTransfer :: Owner
-> Repo
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
acceptRepoTransfer (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer/accept"]
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest AcceptRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
AcceptRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data AcceptRepoTransfer
instance Produces AcceptRepoTransfer MimeJSON
createCurrentUserRepo
:: (Consumes CreateCurrentUserRepo MimeJSON)
=> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
createCurrentUserRepo :: Consumes CreateCurrentUserRepo MimeJSON =>
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
createCurrentUserRepo =
Method
-> [ByteString]
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/repos"]
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateCurrentUserRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data CreateCurrentUserRepo
instance HasBodyParam CreateCurrentUserRepo CreateRepoOption
instance Consumes CreateCurrentUserRepo MimeJSON
instance Produces CreateCurrentUserRepo MimeJSON
createFork
:: (Consumes CreateFork contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest CreateFork contentType Repository MimeJSON
createFork :: forall contentType.
Consumes CreateFork contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest CreateFork contentType Repository MimeJSON
createFork ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/forks"]
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest CreateFork contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateFork contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data CreateFork
instance HasBodyParam CreateFork CreateForkOption
instance Consumes CreateFork MimeJSON
instance Consumes CreateFork MimePlainText
instance Produces CreateFork MimeJSON
createRepoVariable
:: (Consumes CreateRepoVariable contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
createRepoVariable :: forall contentType.
Consumes CreateRepoVariable contentType =>
ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
createRepoVariable ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest CreateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
CreateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data CreateRepoVariable
instance HasBodyParam CreateRepoVariable CreateVariableOption
instance Consumes CreateRepoVariable MimeJSON
instance Consumes CreateRepoVariable MimePlainText
instance Produces CreateRepoVariable MimeNoContent
deleteRepoSecret
:: Owner
-> Repo
-> Secretname
-> GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
deleteRepoSecret :: Owner
-> Repo
-> Secretname
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
deleteRepoSecret (Owner Text
owner) (Repo Text
repo) (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest DeleteRepoSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteRepoSecret MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data DeleteRepoSecret
instance Produces DeleteRepoSecret MimeNoContent
deleteRepoVariable
:: Owner
-> Repo
-> Variablename
-> GiteaRequest DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
deleteRepoVariable :: Owner
-> Repo
-> Variablename
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
deleteRepoVariable (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data DeleteRepoVariable
instance Produces DeleteRepoVariable MimeJSON
generateRepo
:: (Consumes GenerateRepo MimeJSON)
=> TemplateOwner
-> TemplateRepo
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
generateRepo :: Consumes GenerateRepo MimeJSON =>
TemplateOwner
-> TemplateRepo
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
generateRepo (TemplateOwner Text
templateOwner) (TemplateRepo Text
templateRepo) =
Method
-> [ByteString]
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
templateOwner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
templateRepo,ByteString
"/generate"]
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GenerateRepo MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GenerateRepo
instance HasBodyParam GenerateRepo GenerateRepoOption
instance Consumes GenerateRepo MimeJSON
instance Produces GenerateRepo MimeJSON
getAnnotatedTag
:: Owner
-> Repo
-> Sha
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
getAnnotatedTag :: Owner
-> Repo
-> Sha
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
getAnnotatedTag (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetAnnotatedTag MimeNoContent AnnotatedTag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetAnnotatedTag
instance Produces GetAnnotatedTag MimeJSON
getBlob
:: Owner
-> Repo
-> Sha
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
getBlob :: Owner
-> Repo
-> Sha
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
getBlob (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/blobs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetBlob MimeNoContent GitBlobResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetBlob
instance Produces GetBlob MimeJSON
getRepoVariable
:: Owner
-> Repo
-> Variablename
-> GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
getRepoVariable :: Owner
-> Repo
-> Variablename
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
getRepoVariable (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetRepoVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetRepoVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetRepoVariable
instance Produces GetRepoVariable MimeJSON
getRepoVariablesList
:: Owner
-> Repo
-> GiteaRequest GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
getRepoVariablesList :: Owner
-> Repo
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
getRepoVariablesList (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables"]
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetRepoVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetRepoVariablesList
instance HasOptionalParam GetRepoVariablesList Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetRepoVariablesList contentType res accept
-> Page -> GiteaRequest GetRepoVariablesList contentType res accept
applyOptionalParam GiteaRequest GetRepoVariablesList contentType res accept
req (Page Int
xs) =
GiteaRequest GetRepoVariablesList contentType res accept
req GiteaRequest GetRepoVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetRepoVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam GetRepoVariablesList Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetRepoVariablesList contentType res accept
-> Limit
-> GiteaRequest GetRepoVariablesList contentType res accept
applyOptionalParam GiteaRequest GetRepoVariablesList contentType res accept
req (Limit Int
xs) =
GiteaRequest GetRepoVariablesList contentType res accept
req GiteaRequest GetRepoVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetRepoVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces GetRepoVariablesList MimeJSON
getTree
:: Owner
-> Repo
-> Sha
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
getTree :: Owner
-> Repo
-> Sha
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
getTree (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/trees/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetTree MimeNoContent GitTreeResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetTree
instance HasOptionalParam GetTree Recursive where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> Recursive -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (Recursive Bool
xs) =
GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"recursive", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam GetTree Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> Page -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (Page Int
xs) =
GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam GetTree PerPage where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetTree contentType res accept
-> PerPage -> GiteaRequest GetTree contentType res accept
applyOptionalParam GiteaRequest GetTree contentType res accept
req (PerPage Int
xs) =
GiteaRequest GetTree contentType res accept
req GiteaRequest GetTree contentType res accept
-> [QueryItem] -> GiteaRequest GetTree contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"per_page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces GetTree MimeJSON
listActionTasks
:: Owner
-> Repo
-> GiteaRequest ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
listActionTasks :: Owner
-> Repo
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
listActionTasks (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/tasks"]
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
ListActionTasks MimeNoContent ActionTaskResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data ListActionTasks
instance HasOptionalParam ListActionTasks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest ListActionTasks contentType res accept
-> Page -> GiteaRequest ListActionTasks contentType res accept
applyOptionalParam GiteaRequest ListActionTasks contentType res accept
req (Page Int
xs) =
GiteaRequest ListActionTasks contentType res accept
req GiteaRequest ListActionTasks contentType res accept
-> [QueryItem]
-> GiteaRequest ListActionTasks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListActionTasks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest ListActionTasks contentType res accept
-> Limit -> GiteaRequest ListActionTasks contentType res accept
applyOptionalParam GiteaRequest ListActionTasks contentType res accept
req (Limit Int
xs) =
GiteaRequest ListActionTasks contentType res accept
req GiteaRequest ListActionTasks contentType res accept
-> [QueryItem]
-> GiteaRequest ListActionTasks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces ListActionTasks MimeJSON
listForks
:: Owner
-> Repo
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
listForks :: Owner
-> Repo
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
listForks (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/forks"]
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest ListForks MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data ListForks
instance HasOptionalParam ListForks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest ListForks contentType res accept
-> Page -> GiteaRequest ListForks contentType res accept
applyOptionalParam GiteaRequest ListForks contentType res accept
req (Page Int
xs) =
GiteaRequest ListForks contentType res accept
req GiteaRequest ListForks contentType res accept
-> [QueryItem] -> GiteaRequest ListForks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListForks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest ListForks contentType res accept
-> Limit -> GiteaRequest ListForks contentType res accept
applyOptionalParam GiteaRequest ListForks contentType res accept
req (Limit Int
xs) =
GiteaRequest ListForks contentType res accept
req GiteaRequest ListForks contentType res accept
-> [QueryItem] -> GiteaRequest ListForks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces ListForks MimeJSON
rejectRepoTransfer
:: Owner
-> Repo
-> GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
rejectRepoTransfer :: Owner
-> Repo
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
rejectRepoTransfer (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer/reject"]
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RejectRepoTransfer MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RejectRepoTransfer MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RejectRepoTransfer
instance Produces RejectRepoTransfer MimeJSON
repoAddCollaborator
:: (Consumes RepoAddCollaborator contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Collaborator
-> GiteaRequest RepoAddCollaborator contentType NoContent MimeNoContent
repoAddCollaborator :: forall contentType.
Consumes RepoAddCollaborator contentType =>
ContentType contentType
-> Owner
-> Repo
-> Collaborator
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
repoAddCollaborator ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
Method
-> [ByteString]
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoAddCollaborator contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoAddCollaborator
instance HasBodyParam RepoAddCollaborator AddCollaboratorOption
instance Consumes RepoAddCollaborator MimeJSON
instance Consumes RepoAddCollaborator MimePlainText
instance Produces RepoAddCollaborator MimeNoContent
repoAddPushMirror
:: (Consumes RepoAddPushMirror MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
repoAddPushMirror :: Consumes RepoAddPushMirror MimeJSON =>
Owner
-> Repo
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
repoAddPushMirror (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors"]
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddPushMirror MimeJSON PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoAddPushMirror
instance HasBodyParam RepoAddPushMirror CreatePushMirrorOption
instance Consumes RepoAddPushMirror MimeJSON
instance Produces RepoAddPushMirror MimeJSON
repoAddTeam
:: Owner
-> Repo
-> Team2
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
repoAddTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
repoAddTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
Method
-> [ByteString]
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoAddTeam
instance Produces RepoAddTeam MimeNoContent
repoAddTopic
:: Owner
-> Repo
-> TopicText
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
repoAddTopic :: Owner
-> Repo
-> TopicText
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
repoAddTopic (Owner Text
owner) (Repo Text
repo) (TopicText Text
topic) =
Method
-> [ByteString]
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
topic]
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoAddTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoAddTopic
instance Produces RepoAddTopic MimeNoContent
repoApplyDiffPatch
:: (Consumes RepoApplyDiffPatch MimeJSON, MimeRender MimeJSON UpdateFileOptions)
=> UpdateFileOptions
-> Owner
-> Repo
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
repoApplyDiffPatch :: (Consumes RepoApplyDiffPatch MimeJSON,
MimeRender MimeJSON UpdateFileOptions) =>
UpdateFileOptions
-> Owner
-> Repo
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
repoApplyDiffPatch UpdateFileOptions
body (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/diffpatch"]
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
-> UpdateFileOptions
-> GiteaRequest RepoApplyDiffPatch MimeJSON FileResponse MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoApplyDiffPatch contentType,
MimeRender contentType UpdateFileOptions) =>
GiteaRequest RepoApplyDiffPatch contentType res accept
-> UpdateFileOptions
-> GiteaRequest RepoApplyDiffPatch contentType res accept
`setBodyParam` UpdateFileOptions
body
data RepoApplyDiffPatch
instance HasBodyParam RepoApplyDiffPatch UpdateFileOptions
instance Consumes RepoApplyDiffPatch MimeJSON
instance Produces RepoApplyDiffPatch MimeJSON
repoCancelScheduledAutoMerge
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
repoCancelScheduledAutoMerge :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
repoCancelScheduledAutoMerge (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCancelScheduledAutoMerge MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCancelScheduledAutoMerge
instance Produces RepoCancelScheduledAutoMerge MimeNoContent
repoChangeFiles
:: (Consumes RepoChangeFiles MimeJSON, MimeRender MimeJSON ChangeFilesOptions)
=> ChangeFilesOptions
-> Owner
-> Repo
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
repoChangeFiles :: (Consumes RepoChangeFiles MimeJSON,
MimeRender MimeJSON ChangeFilesOptions) =>
ChangeFilesOptions
-> Owner
-> Repo
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
repoChangeFiles ChangeFilesOptions
body (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents"]
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
-> ChangeFilesOptions
-> GiteaRequest RepoChangeFiles MimeJSON FilesResponse MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoChangeFiles contentType,
MimeRender contentType ChangeFilesOptions) =>
GiteaRequest RepoChangeFiles contentType res accept
-> ChangeFilesOptions
-> GiteaRequest RepoChangeFiles contentType res accept
`setBodyParam` ChangeFilesOptions
body
data RepoChangeFiles
instance HasBodyParam RepoChangeFiles ChangeFilesOptions
instance Consumes RepoChangeFiles MimeJSON
instance Produces RepoChangeFiles MimeJSON
repoCheckCollaborator
:: Owner
-> Repo
-> Collaborator
-> GiteaRequest RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
repoCheckCollaborator :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
repoCheckCollaborator (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
Method
-> [ByteString]
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCheckCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCheckCollaborator
instance Produces RepoCheckCollaborator MimeNoContent
repoCheckTeam
:: Owner
-> Repo
-> Team2
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
repoCheckTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
repoCheckTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
Method
-> [ByteString]
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCheckTeam MimeNoContent Team MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCheckTeam
instance Produces RepoCheckTeam MimeJSON
repoCompareDiff
:: Owner
-> Repo
-> Basehead
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
repoCompareDiff :: Owner
-> Repo
-> Basehead
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
repoCompareDiff (Owner Text
owner) (Repo Text
repo) (Basehead Text
basehead) =
Method
-> [ByteString]
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/compare/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
basehead]
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCompareDiff MimeNoContent Compare MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCompareDiff
instance Produces RepoCompareDiff MimeJSON
repoCreateBranch
:: (Consumes RepoCreateBranch MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
repoCreateBranch :: Consumes RepoCreateBranch MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
repoCreateBranch (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches"]
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateBranch MimeJSON Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateBranch
instance HasBodyParam RepoCreateBranch CreateBranchRepoOption
instance Consumes RepoCreateBranch MimeJSON
instance Produces RepoCreateBranch MimeJSON
repoCreateBranchProtection
:: (Consumes RepoCreateBranchProtection MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
repoCreateBranchProtection :: Consumes RepoCreateBranchProtection MimeJSON =>
Owner
-> Repo
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
repoCreateBranchProtection (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections"]
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCreateBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateBranchProtection
instance HasBodyParam RepoCreateBranchProtection CreateBranchProtectionOption
instance Consumes RepoCreateBranchProtection MimeJSON
instance Produces RepoCreateBranchProtection MimeJSON
repoCreateFile
:: (Consumes RepoCreateFile MimeJSON, MimeRender MimeJSON CreateFileOptions)
=> CreateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
repoCreateFile :: (Consumes RepoCreateFile MimeJSON,
MimeRender MimeJSON CreateFileOptions) =>
CreateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
repoCreateFile CreateFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
-> CreateFileOptions
-> GiteaRequest RepoCreateFile MimeJSON FileResponse MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoCreateFile contentType,
MimeRender contentType CreateFileOptions) =>
GiteaRequest RepoCreateFile contentType res accept
-> CreateFileOptions
-> GiteaRequest RepoCreateFile contentType res accept
`setBodyParam` CreateFileOptions
body
data RepoCreateFile
instance HasBodyParam RepoCreateFile CreateFileOptions
instance Consumes RepoCreateFile MimeJSON
instance Produces RepoCreateFile MimeJSON
repoCreateHook
:: (Consumes RepoCreateHook MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
repoCreateHook :: Consumes RepoCreateHook MimeJSON =>
Owner -> Repo -> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
repoCreateHook (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks"]
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateHook MimeJSON Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateHook
instance HasBodyParam RepoCreateHook CreateHookOption
instance Consumes RepoCreateHook MimeJSON
instance Produces RepoCreateHook MimeJSON
repoCreateKey
:: (Consumes RepoCreateKey MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
repoCreateKey :: Consumes RepoCreateKey MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
repoCreateKey (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys"]
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateKey MimeJSON DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateKey
instance HasBodyParam RepoCreateKey CreateKeyOption
instance Consumes RepoCreateKey MimeJSON
instance Produces RepoCreateKey MimeJSON
repoCreatePullRequest
:: (Consumes RepoCreatePullRequest MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
repoCreatePullRequest :: Consumes RepoCreatePullRequest MimeJSON =>
Owner
-> Repo
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
repoCreatePullRequest (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls"]
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreatePullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreatePullRequest
instance HasBodyParam RepoCreatePullRequest CreatePullRequestOption
instance Consumes RepoCreatePullRequest MimeJSON
instance Produces RepoCreatePullRequest MimeJSON
repoCreatePullReview
:: (Consumes RepoCreatePullReview contentType, MimeRender contentType CreatePullReviewOptions)
=> ContentType contentType
-> CreatePullReviewOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
repoCreatePullReview :: forall contentType.
(Consumes RepoCreatePullReview contentType,
MimeRender contentType CreatePullReviewOptions) =>
ContentType contentType
-> CreatePullReviewOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
repoCreatePullReview ContentType contentType
_ CreatePullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews"]
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoCreatePullReview contentType PullReview MimeJSON
-> CreatePullReviewOptions
-> GiteaRequest
RepoCreatePullReview contentType PullReview MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoCreatePullReview contentType,
MimeRender contentType CreatePullReviewOptions) =>
GiteaRequest RepoCreatePullReview contentType res accept
-> CreatePullReviewOptions
-> GiteaRequest RepoCreatePullReview contentType res accept
`setBodyParam` CreatePullReviewOptions
body
data RepoCreatePullReview
instance HasBodyParam RepoCreatePullReview CreatePullReviewOptions
instance Consumes RepoCreatePullReview MimeJSON
instance Consumes RepoCreatePullReview MimePlainText
instance Produces RepoCreatePullReview MimeJSON
repoCreatePullReviewRequests
:: (Consumes RepoCreatePullReviewRequests contentType, MimeRender contentType PullReviewRequestOptions)
=> ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
repoCreatePullReviewRequests :: forall contentType.
(Consumes RepoCreatePullReviewRequests contentType,
MimeRender contentType PullReviewRequestOptions) =>
ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
repoCreatePullReviewRequests ContentType contentType
_ PullReviewRequestOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/requested_reviewers"]
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
-> PullReviewRequestOptions
-> GiteaRequest
RepoCreatePullReviewRequests contentType [PullReview] MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoCreatePullReviewRequests contentType,
MimeRender contentType PullReviewRequestOptions) =>
GiteaRequest RepoCreatePullReviewRequests contentType res accept
-> PullReviewRequestOptions
-> GiteaRequest RepoCreatePullReviewRequests contentType res accept
`setBodyParam` PullReviewRequestOptions
body
data RepoCreatePullReviewRequests
instance HasBodyParam RepoCreatePullReviewRequests PullReviewRequestOptions
instance Consumes RepoCreatePullReviewRequests MimeJSON
instance Consumes RepoCreatePullReviewRequests MimePlainText
instance Produces RepoCreatePullReviewRequests MimeJSON
repoCreateRelease
:: (Consumes RepoCreateRelease MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
repoCreateRelease :: Consumes RepoCreateRelease MimeJSON =>
Owner
-> Repo -> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
repoCreateRelease (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases"]
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateRelease
instance HasBodyParam RepoCreateRelease CreateReleaseOption
instance Consumes RepoCreateRelease MimeJSON
instance Produces RepoCreateRelease MimeJSON
repoCreateReleaseAttachment
:: (Consumes RepoCreateReleaseAttachment contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest RepoCreateReleaseAttachment contentType Attachment MimeJSON
repoCreateReleaseAttachment :: forall contentType.
Consumes RepoCreateReleaseAttachment contentType =>
ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
repoCreateReleaseAttachment ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets"]
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCreateReleaseAttachment contentType Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateReleaseAttachment
instance HasOptionalParam RepoCreateReleaseAttachment Attachment2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Attachment2
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
applyOptionalParam GiteaRequest RepoCreateReleaseAttachment contentType res accept
req (Attachment2 FilePath
xs) =
GiteaRequest RepoCreateReleaseAttachment contentType res accept
req GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Part
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> Part -> GiteaRequest req contentType res accept
`_addMultiFormPart` Text -> FilePath -> Part
NH.partFileSource Text
"attachment" FilePath
xs
instance HasOptionalParam RepoCreateReleaseAttachment Name where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> Name
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
applyOptionalParam GiteaRequest RepoCreateReleaseAttachment contentType res accept
req (Name Text
xs) =
GiteaRequest RepoCreateReleaseAttachment contentType res accept
req GiteaRequest RepoCreateReleaseAttachment contentType res accept
-> [QueryItem]
-> GiteaRequest RepoCreateReleaseAttachment contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"name", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Consumes RepoCreateReleaseAttachment MimeOctetStream
instance Consumes RepoCreateReleaseAttachment MimeMultipartFormData
instance Produces RepoCreateReleaseAttachment MimeJSON
repoCreateStatus
:: (Consumes RepoCreateStatus contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Sha
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
repoCreateStatus :: forall contentType.
Consumes RepoCreateStatus contentType =>
ContentType contentType
-> Owner
-> Repo
-> Sha
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
repoCreateStatus ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/statuses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateStatus contentType CommitStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateStatus
instance HasBodyParam RepoCreateStatus CreateStatusOption
instance Consumes RepoCreateStatus MimeJSON
instance Consumes RepoCreateStatus MimePlainText
instance Produces RepoCreateStatus MimeJSON
repoCreateTag
:: (Consumes RepoCreateTag contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
repoCreateTag :: forall contentType.
Consumes RepoCreateTag contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
repoCreateTag ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags"]
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateTag contentType Tag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateTag contentType Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateTag
instance HasBodyParam RepoCreateTag CreateTagOption
instance Consumes RepoCreateTag MimeJSON
instance Consumes RepoCreateTag MimePlainText
instance Produces RepoCreateTag MimeJSON
repoCreateTagProtection
:: (Consumes RepoCreateTagProtection MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoCreateTagProtection MimeJSON TagProtection MimeJSON
repoCreateTagProtection :: Consumes RepoCreateTagProtection MimeJSON =>
Owner
-> Repo
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
repoCreateTagProtection (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections"]
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoCreateTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateTagProtection
instance HasBodyParam RepoCreateTagProtection CreateTagProtectionOption
instance Consumes RepoCreateTagProtection MimeJSON
instance Produces RepoCreateTagProtection MimeJSON
repoCreateWikiPage
:: (Consumes RepoCreateWikiPage MimeJSON)
=> Accept accept
-> Owner
-> Repo
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
repoCreateWikiPage :: forall accept.
Consumes RepoCreateWikiPage MimeJSON =>
Accept accept
-> Owner
-> Repo
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
repoCreateWikiPage Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/new"]
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoCreateWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoCreateWikiPage
instance HasBodyParam RepoCreateWikiPage CreateWikiPageOptions
instance Consumes RepoCreateWikiPage MimeJSON
instance Produces RepoCreateWikiPage MimeTextHtml
instance Produces RepoCreateWikiPage MimeJSON
repoDelete
:: Owner
-> Repo
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
repoDelete :: Owner
-> Repo
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
repoDelete (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDelete MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDelete
instance Produces RepoDelete MimeNoContent
repoDeleteAvatar
:: Owner
-> Repo
-> GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
repoDeleteAvatar :: Owner
-> Repo
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
repoDeleteAvatar (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/avatar"]
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteAvatar MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteAvatar
instance Produces RepoDeleteAvatar MimeNoContent
repoDeleteBranch
:: Owner
-> Repo
-> Branch2
-> GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
repoDeleteBranch :: Owner
-> Repo
-> Branch2
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
repoDeleteBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteBranch MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteBranch MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteBranch
instance Produces RepoDeleteBranch MimeNoContent
repoDeleteBranchProtection
:: Owner
-> Repo
-> Name
-> GiteaRequest RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
repoDeleteBranchProtection :: Owner
-> Repo
-> Name
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
repoDeleteBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteBranchProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteBranchProtection
instance Produces RepoDeleteBranchProtection MimeNoContent
repoDeleteCollaborator
:: Owner
-> Repo
-> Collaborator
-> GiteaRequest RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
repoDeleteCollaborator :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
repoDeleteCollaborator (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator]
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteCollaborator MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteCollaborator
instance Produces RepoDeleteCollaborator MimeNoContent
repoDeleteFile
:: (Consumes RepoDeleteFile MimeJSON, MimeRender MimeJSON DeleteFileOptions)
=> DeleteFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
repoDeleteFile :: (Consumes RepoDeleteFile MimeJSON,
MimeRender MimeJSON DeleteFileOptions) =>
DeleteFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
repoDeleteFile DeleteFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
-> DeleteFileOptions
-> GiteaRequest RepoDeleteFile MimeJSON FileDeleteResponse MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoDeleteFile contentType,
MimeRender contentType DeleteFileOptions) =>
GiteaRequest RepoDeleteFile contentType res accept
-> DeleteFileOptions
-> GiteaRequest RepoDeleteFile contentType res accept
`setBodyParam` DeleteFileOptions
body
data RepoDeleteFile
instance HasBodyParam RepoDeleteFile DeleteFileOptions
instance Consumes RepoDeleteFile MimeJSON
instance Produces RepoDeleteFile MimeJSON
repoDeleteGitHook
:: Owner
-> Repo
-> IdText
-> GiteaRequest RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
repoDeleteGitHook :: Owner
-> Repo
-> IdText
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
repoDeleteGitHook (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteGitHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteGitHook
instance Produces RepoDeleteGitHook MimeNoContent
repoDeleteHook
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
repoDeleteHook :: Owner
-> Repo
-> Id
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
repoDeleteHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteHook
instance Produces RepoDeleteHook MimeNoContent
repoDeleteKey
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
repoDeleteKey :: Owner
-> Repo
-> Id
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
repoDeleteKey (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteKey MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteKey
instance Produces RepoDeleteKey MimeNoContent
repoDeletePullReview
:: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoDeletePullReview MimeNoContent NoContent MimeNoContent
repoDeletePullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
repoDeletePullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeletePullReview MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeletePullReview
instance Produces RepoDeletePullReview MimeNoContent
repoDeletePullReviewRequests
:: (Consumes RepoDeletePullReviewRequests contentType, MimeRender contentType PullReviewRequestOptions)
=> ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest RepoDeletePullReviewRequests contentType NoContent MimeNoContent
repoDeletePullReviewRequests :: forall contentType.
(Consumes RepoDeletePullReviewRequests contentType,
MimeRender contentType PullReviewRequestOptions) =>
ContentType contentType
-> PullReviewRequestOptions
-> Owner
-> Repo
-> Index
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
repoDeletePullReviewRequests ContentType contentType
_ PullReviewRequestOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/requested_reviewers"]
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
-> PullReviewRequestOptions
-> GiteaRequest
RepoDeletePullReviewRequests contentType NoContent MimeNoContent
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoDeletePullReviewRequests contentType,
MimeRender contentType PullReviewRequestOptions) =>
GiteaRequest RepoDeletePullReviewRequests contentType res accept
-> PullReviewRequestOptions
-> GiteaRequest RepoDeletePullReviewRequests contentType res accept
`setBodyParam` PullReviewRequestOptions
body
data RepoDeletePullReviewRequests
instance HasBodyParam RepoDeletePullReviewRequests PullReviewRequestOptions
instance Consumes RepoDeletePullReviewRequests MimeJSON
instance Consumes RepoDeletePullReviewRequests MimePlainText
instance Produces RepoDeletePullReviewRequests MimeNoContent
repoDeletePushMirror
:: Owner
-> Repo
-> Name
-> GiteaRequest RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
repoDeletePushMirror :: Owner
-> Repo
-> Name
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
repoDeletePushMirror (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeletePushMirror MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeletePushMirror
instance Produces RepoDeletePushMirror MimeNoContent
repoDeleteRelease
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoDeleteRelease MimeNoContent NoContent MimeNoContent
repoDeleteRelease :: Owner
-> Repo
-> Id
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
repoDeleteRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteRelease MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteRelease
instance Produces RepoDeleteRelease MimeNoContent
repoDeleteReleaseAttachment
:: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
repoDeleteReleaseAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
repoDeleteReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteReleaseAttachment MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteReleaseAttachment
instance Produces RepoDeleteReleaseAttachment MimeNoContent
repoDeleteReleaseByTag
:: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
repoDeleteReleaseByTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
repoDeleteReleaseByTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteReleaseByTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteReleaseByTag
instance Produces RepoDeleteReleaseByTag MimeNoContent
repoDeleteTag
:: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
repoDeleteTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
repoDeleteTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
Method
-> [ByteString]
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoDeleteTag MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteTag
instance Produces RepoDeleteTag MimeNoContent
repoDeleteTagProtection
:: Owner
-> Repo
-> IdInt
-> GiteaRequest RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
repoDeleteTagProtection :: Owner
-> Repo
-> IdInt
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
repoDeleteTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteTagProtection MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteTagProtection
instance Produces RepoDeleteTagProtection MimeNoContent
repoDeleteTeam
:: Owner
-> Repo
-> Team2
-> GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
repoDeleteTeam :: Owner
-> Repo
-> Team2
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
repoDeleteTeam (Owner Text
owner) (Repo Text
repo) (Team2 Text
team) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
team]
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteTeam MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteTeam
instance Produces RepoDeleteTeam MimeNoContent
repoDeleteTopic
:: Owner
-> Repo
-> TopicText
-> GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
repoDeleteTopic :: Owner
-> Repo
-> TopicText
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
repoDeleteTopic (Owner Text
owner) (Repo Text
repo) (TopicText Text
topic) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
topic]
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDeleteTopic MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteTopic MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteTopic
instance Produces RepoDeleteTopic MimeNoContent
repoDeleteWikiPage
:: Owner
-> Repo
-> PageName
-> GiteaRequest RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
repoDeleteWikiPage :: Owner
-> Repo
-> PageName
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
repoDeleteWikiPage (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
Method
-> [ByteString]
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDeleteWikiPage MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDeleteWikiPage
instance Produces RepoDeleteWikiPage MimeNoContent
repoDismissPullReview
:: (Consumes RepoDismissPullReview contentType, MimeRender contentType DismissPullReviewOptions)
=> ContentType contentType
-> DismissPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
repoDismissPullReview :: forall contentType.
(Consumes RepoDismissPullReview contentType,
MimeRender contentType DismissPullReviewOptions) =>
ContentType contentType
-> DismissPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
repoDismissPullReview ContentType contentType
_ DismissPullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/dismissals"]
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoDismissPullReview contentType PullReview MimeJSON
-> DismissPullReviewOptions
-> GiteaRequest
RepoDismissPullReview contentType PullReview MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoDismissPullReview contentType,
MimeRender contentType DismissPullReviewOptions) =>
GiteaRequest RepoDismissPullReview contentType res accept
-> DismissPullReviewOptions
-> GiteaRequest RepoDismissPullReview contentType res accept
`setBodyParam` DismissPullReviewOptions
body
data RepoDismissPullReview
instance HasBodyParam RepoDismissPullReview DismissPullReviewOptions
instance Consumes RepoDismissPullReview MimeJSON
instance Consumes RepoDismissPullReview MimePlainText
instance Produces RepoDismissPullReview MimeJSON
repoDownloadCommitDiffOrPatch
:: Owner
-> Repo
-> Sha
-> DiffType
-> GiteaRequest RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadCommitDiffOrPatch :: Owner
-> Repo
-> Sha
-> DiffType
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadCommitDiffOrPatch (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) (DiffType E'DiffType
diffType) =
Method
-> [ByteString]
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha,ByteString
".",E'DiffType -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath E'DiffType
diffType]
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDownloadCommitDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDownloadCommitDiffOrPatch
instance Produces RepoDownloadCommitDiffOrPatch MimePlainText
repoDownloadPullDiffOrPatch
:: Owner
-> Repo
-> Index
-> DiffType
-> GiteaRequest RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadPullDiffOrPatch :: Owner
-> Repo
-> Index
-> DiffType
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
repoDownloadPullDiffOrPatch (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (DiffType E'DiffType
diffType) =
Method
-> [ByteString]
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
".",E'DiffType -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath E'DiffType
diffType]
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoDownloadPullDiffOrPatch MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoDownloadPullDiffOrPatch
instance HasOptionalParam RepoDownloadPullDiffOrPatch ParamBinary where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
-> ParamBinary
-> GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
applyOptionalParam GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
req (ParamBinary Bool
xs) =
GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
req GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
-> [QueryItem]
-> GiteaRequest RepoDownloadPullDiffOrPatch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"binary", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces RepoDownloadPullDiffOrPatch MimePlainText
repoEdit
:: (Consumes RepoEdit contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoEdit contentType Repository MimeJSON
repoEdit :: forall contentType.
Consumes RepoEdit contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoEdit contentType Repository MimeJSON
repoEdit ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEdit contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEdit contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEdit
instance HasBodyParam RepoEdit EditRepoOption
instance Consumes RepoEdit MimeJSON
instance Consumes RepoEdit MimePlainText
instance Produces RepoEdit MimeJSON
repoEditBranchProtection
:: (Consumes RepoEditBranchProtection MimeJSON)
=> Owner
-> Repo
-> Name
-> GiteaRequest RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
repoEditBranchProtection :: Consumes RepoEditBranchProtection MimeJSON =>
Owner
-> Repo
-> Name
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
repoEditBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
Method
-> [ByteString]
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoEditBranchProtection MimeJSON BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditBranchProtection
instance HasBodyParam RepoEditBranchProtection EditBranchProtectionOption
instance Consumes RepoEditBranchProtection MimeJSON
instance Produces RepoEditBranchProtection MimeJSON
repoEditGitHook
:: (Consumes RepoEditGitHook contentType)
=> ContentType contentType
-> Owner
-> Repo
-> IdText
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
repoEditGitHook :: forall contentType.
Consumes RepoEditGitHook contentType =>
ContentType contentType
-> Owner
-> Repo
-> IdText
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
repoEditGitHook ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
Method
-> [ByteString]
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditGitHook contentType GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditGitHook
instance HasBodyParam RepoEditGitHook EditGitHookOption
instance Consumes RepoEditGitHook MimeJSON
instance Consumes RepoEditGitHook MimePlainText
instance Produces RepoEditGitHook MimeJSON
repoEditHook
:: (Consumes RepoEditHook contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
repoEditHook :: forall contentType.
Consumes RepoEditHook contentType =>
ContentType contentType
-> Owner
-> Repo
-> Id
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
repoEditHook ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditHook contentType Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditHook contentType Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditHook
instance HasBodyParam RepoEditHook EditHookOption
instance Consumes RepoEditHook MimeJSON
instance Consumes RepoEditHook MimePlainText
instance Produces RepoEditHook MimeJSON
repoEditPullRequest
:: (Consumes RepoEditPullRequest MimeJSON)
=> Owner
-> Repo
-> Index
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
repoEditPullRequest :: Consumes RepoEditPullRequest MimeJSON =>
Owner
-> Repo
-> Index
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
repoEditPullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditPullRequest MimeJSON PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditPullRequest
instance HasBodyParam RepoEditPullRequest EditPullRequestOption
instance Consumes RepoEditPullRequest MimeJSON
instance Produces RepoEditPullRequest MimeJSON
repoEditRelease
:: (Consumes RepoEditRelease MimeJSON)
=> Owner
-> Repo
-> Id
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
repoEditRelease :: Consumes RepoEditRelease MimeJSON =>
Owner
-> Repo
-> Id
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
repoEditRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditRelease MimeJSON Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditRelease
instance HasBodyParam RepoEditRelease EditReleaseOption
instance Consumes RepoEditRelease MimeJSON
instance Produces RepoEditRelease MimeJSON
repoEditReleaseAttachment
:: (Consumes RepoEditReleaseAttachment MimeJSON)
=> Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
repoEditReleaseAttachment :: Consumes RepoEditReleaseAttachment MimeJSON =>
Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
repoEditReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
Method
-> [ByteString]
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoEditReleaseAttachment MimeJSON Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditReleaseAttachment
instance HasBodyParam RepoEditReleaseAttachment EditAttachmentOptions
instance Consumes RepoEditReleaseAttachment MimeJSON
instance Produces RepoEditReleaseAttachment MimeJSON
repoEditTagProtection
:: (Consumes RepoEditTagProtection MimeJSON)
=> Owner
-> Repo
-> IdInt
-> GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
repoEditTagProtection :: Consumes RepoEditTagProtection MimeJSON =>
Owner
-> Repo
-> IdInt
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
repoEditTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditTagProtection MimeJSON TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoEditTagProtection MimeJSON TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditTagProtection
instance HasBodyParam RepoEditTagProtection EditTagProtectionOption
instance Consumes RepoEditTagProtection MimeJSON
instance Produces RepoEditTagProtection MimeJSON
repoEditWikiPage
:: (Consumes RepoEditWikiPage MimeJSON)
=> Accept accept
-> Owner
-> Repo
-> PageName
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
repoEditWikiPage :: forall accept.
Consumes RepoEditWikiPage MimeJSON =>
Accept accept
-> Owner
-> Repo
-> PageName
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
repoEditWikiPage Accept accept
_ (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
Method
-> [ByteString]
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoEditWikiPage MimeJSON WikiPage accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoEditWikiPage
instance HasBodyParam RepoEditWikiPage CreateWikiPageOptions
instance Consumes RepoEditWikiPage MimeJSON
instance Produces RepoEditWikiPage MimeTextHtml
instance Produces RepoEditWikiPage MimeJSON
repoGet
:: Owner
-> Repo
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
repoGet :: Owner
-> Repo -> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
repoGet (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGet MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGet MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGet
instance Produces RepoGet MimeJSON
repoGetAllCommits
:: Owner
-> Repo
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
repoGetAllCommits :: Owner
-> Repo
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
repoGetAllCommits (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits"]
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetAllCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetAllCommits
instance HasOptionalParam RepoGetAllCommits Sha where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Sha -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Sha Text
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sha", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoGetAllCommits Path where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Path -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Path Text
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoGetAllCommits Stat where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Stat -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Stat Bool
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stat", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetAllCommits Verification where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Verification
-> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Verification Bool
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetAllCommits Files where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Files -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Files Bool
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetAllCommits Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Page -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetAllCommits Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Limit -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetAllCommits Not where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetAllCommits contentType res accept
-> Not -> GiteaRequest RepoGetAllCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetAllCommits contentType res accept
req (Not Text
xs) =
GiteaRequest RepoGetAllCommits contentType res accept
req GiteaRequest RepoGetAllCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetAllCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"not", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetAllCommits MimeJSON
repoGetArchive
:: Owner
-> Repo
-> Archive
-> GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
repoGetArchive :: Owner
-> Repo
-> Archive
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
repoGetArchive (Owner Text
owner) (Repo Text
repo) (Archive Text
archive) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/archive/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
archive]
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetArchive MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetArchive MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetArchive
instance Produces RepoGetArchive MimeNoContent
repoGetAssignees
:: Owner
-> Repo
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
repoGetAssignees :: Owner
-> Repo
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
repoGetAssignees (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/assignees"]
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetAssignees MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetAssignees
instance Produces RepoGetAssignees MimeJSON
repoGetBranch
:: Owner
-> Repo
-> Branch2
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
repoGetBranch :: Owner
-> Repo
-> Branch2
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
repoGetBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
Method
-> [ByteString]
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetBranch MimeNoContent Branch MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetBranch
instance Produces RepoGetBranch MimeJSON
repoGetBranchProtection
:: Owner
-> Repo
-> Name
-> GiteaRequest RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
repoGetBranchProtection :: Owner
-> Repo
-> Name
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
repoGetBranchProtection (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetBranchProtection MimeNoContent BranchProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetBranchProtection
instance Produces RepoGetBranchProtection MimeJSON
repoGetByID
:: Id
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
repoGetByID :: Id -> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
repoGetByID (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repositories/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetByID MimeNoContent Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetByID
instance Produces RepoGetByID MimeJSON
repoGetCombinedStatusByRef
:: Owner
-> Repo
-> Ref
-> GiteaRequest RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
repoGetCombinedStatusByRef :: Owner
-> Repo
-> Ref
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
repoGetCombinedStatusByRef (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref,ByteString
"/status"]
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetCombinedStatusByRef MimeNoContent CombinedStatus MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetCombinedStatusByRef
instance HasOptionalParam RepoGetCombinedStatusByRef Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> Page
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
applyOptionalParam GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetCombinedStatusByRef Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> Limit
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
applyOptionalParam GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoGetCombinedStatusByRef contentType res accept
req GiteaRequest RepoGetCombinedStatusByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetCombinedStatusByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoGetCombinedStatusByRef MimeJSON
repoGetCommitPullRequest
:: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
repoGetCommitPullRequest :: Owner
-> Repo
-> Sha
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
repoGetCommitPullRequest (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha,ByteString
"/pull"]
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetCommitPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetCommitPullRequest
instance Produces RepoGetCommitPullRequest MimeJSON
repoGetContents
:: Owner
-> Repo
-> Filepath
-> GiteaRequest RepoGetContents MimeNoContent ContentsResponse MimeJSON
repoGetContents :: Owner
-> Repo
-> Filepath
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
repoGetContents (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetContents MimeNoContent ContentsResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetContents
instance HasOptionalParam RepoGetContents Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetContents contentType res accept
-> Ref -> GiteaRequest RepoGetContents contentType res accept
applyOptionalParam GiteaRequest RepoGetContents contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoGetContents contentType res accept
req GiteaRequest RepoGetContents contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetContents contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetContents MimeJSON
repoGetContentsList
:: Owner
-> Repo
-> GiteaRequest RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
repoGetContentsList :: Owner
-> Repo
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
repoGetContentsList (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents"]
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetContentsList MimeNoContent [ContentsResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetContentsList
instance HasOptionalParam RepoGetContentsList Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetContentsList contentType res accept
-> Ref -> GiteaRequest RepoGetContentsList contentType res accept
applyOptionalParam GiteaRequest RepoGetContentsList contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoGetContentsList contentType res accept
req GiteaRequest RepoGetContentsList contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetContentsList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetContentsList MimeJSON
repoGetEditorConfig
:: Owner
-> Repo
-> Filepath
-> GiteaRequest RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
repoGetEditorConfig :: Owner
-> Repo
-> Filepath
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
repoGetEditorConfig (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/editorconfig/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetEditorConfig MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetEditorConfig
instance HasOptionalParam RepoGetEditorConfig Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetEditorConfig contentType res accept
-> Ref -> GiteaRequest RepoGetEditorConfig contentType res accept
applyOptionalParam GiteaRequest RepoGetEditorConfig contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoGetEditorConfig contentType res accept
req GiteaRequest RepoGetEditorConfig contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetEditorConfig contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetEditorConfig MimeNoContent
repoGetGitHook
:: Owner
-> Repo
-> IdText
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
repoGetGitHook :: Owner
-> Repo
-> IdText
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
repoGetGitHook (Owner Text
owner) (Repo Text
repo) (IdText Text
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetGitHook MimeNoContent GitHook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetGitHook
instance Produces RepoGetGitHook MimeJSON
repoGetHook
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
repoGetHook :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
repoGetHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetHook MimeNoContent Hook MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetHook
instance Produces RepoGetHook MimeJSON
repoGetIssueConfig
:: Owner
-> Repo
-> GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
repoGetIssueConfig :: Owner
-> Repo
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
repoGetIssueConfig (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_config"]
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetIssueConfig MimeNoContent IssueConfig MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetIssueConfig
instance Produces RepoGetIssueConfig MimeJSON
repoGetIssueTemplates
:: Owner
-> Repo
-> GiteaRequest RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
repoGetIssueTemplates :: Owner
-> Repo
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
repoGetIssueTemplates (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_templates"]
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetIssueTemplates MimeNoContent [IssueTemplate] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetIssueTemplates
instance Produces RepoGetIssueTemplates MimeJSON
repoGetKey
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
repoGetKey :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
repoGetKey (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetKey MimeNoContent DeployKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetKey
instance Produces RepoGetKey MimeJSON
repoGetLanguages
:: Owner
-> Repo
-> GiteaRequest RepoGetLanguages MimeNoContent ((Map.Map String Integer)) MimeJSON
repoGetLanguages :: Owner
-> Repo
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
repoGetLanguages (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/languages"]
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetLanguages MimeNoContent (Map FilePath Integer) MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetLanguages
instance Produces RepoGetLanguages MimeJSON
repoGetLatestRelease
:: Owner
-> Repo
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
repoGetLatestRelease :: Owner
-> Repo
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
repoGetLatestRelease (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/latest"]
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetLatestRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetLatestRelease
instance Produces RepoGetLatestRelease MimeJSON
repoGetLicenses
:: Owner
-> Repo
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
repoGetLicenses :: Owner
-> Repo
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
repoGetLicenses (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/licenses"]
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetLicenses MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetLicenses
instance Produces RepoGetLicenses MimeJSON
repoGetNote
:: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
repoGetNote :: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
repoGetNote (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/notes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetNote MimeNoContent Note MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetNote
instance HasOptionalParam RepoGetNote Verification where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetNote contentType res accept
-> Verification -> GiteaRequest RepoGetNote contentType res accept
applyOptionalParam GiteaRequest RepoGetNote contentType res accept
req (Verification Bool
xs) =
GiteaRequest RepoGetNote contentType res accept
req GiteaRequest RepoGetNote contentType res accept
-> [QueryItem] -> GiteaRequest RepoGetNote contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetNote Files where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetNote contentType res accept
-> Files -> GiteaRequest RepoGetNote contentType res accept
applyOptionalParam GiteaRequest RepoGetNote contentType res accept
req (Files Bool
xs) =
GiteaRequest RepoGetNote contentType res accept
req GiteaRequest RepoGetNote contentType res accept
-> [QueryItem] -> GiteaRequest RepoGetNote contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces RepoGetNote MimeJSON
repoGetPullRequest
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
repoGetPullRequest :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
repoGetPullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index]
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetPullRequest MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPullRequest MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPullRequest
instance Produces RepoGetPullRequest MimeJSON
repoGetPullRequestByBaseHead
:: Owner
-> Repo
-> Base
-> Head
-> GiteaRequest RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
repoGetPullRequestByBaseHead :: Owner
-> Repo
-> Base
-> Head
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
repoGetPullRequestByBaseHead (Owner Text
owner) (Repo Text
repo) (Base Text
base) (Head Text
head) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
base,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
head]
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPullRequestByBaseHead MimeNoContent PullRequest MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPullRequestByBaseHead
instance Produces RepoGetPullRequestByBaseHead MimeJSON
repoGetPullRequestCommits
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
repoGetPullRequestCommits :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
repoGetPullRequestCommits (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/commits"]
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPullRequestCommits MimeNoContent [Commit] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPullRequestCommits
instance HasOptionalParam RepoGetPullRequestCommits Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Page
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetPullRequestCommits Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Limit
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetPullRequestCommits Verification where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Verification
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Verification Bool
xs) =
GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetPullRequestCommits Files where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestCommits contentType res accept
-> Files
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestCommits contentType res accept
req (Files Bool
xs) =
GiteaRequest RepoGetPullRequestCommits contentType res accept
req GiteaRequest RepoGetPullRequestCommits contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestCommits contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces RepoGetPullRequestCommits MimeJSON
repoGetPullRequestFiles
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
repoGetPullRequestFiles :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
repoGetPullRequestFiles (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/files"]
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPullRequestFiles MimeNoContent [ChangedFile] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPullRequestFiles
instance HasOptionalParam RepoGetPullRequestFiles SkipTo where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> SkipTo
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (SkipTo Text
xs) =
GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"skip-to", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoGetPullRequestFiles Whitespace where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Whitespace
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Whitespace E'Whitespace
xs) =
GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Whitespace) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"whitespace", E'Whitespace -> Maybe E'Whitespace
forall a. a -> Maybe a
Just E'Whitespace
xs)
instance HasOptionalParam RepoGetPullRequestFiles Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Page
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetPullRequestFiles Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetPullRequestFiles contentType res accept
-> Limit
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
applyOptionalParam GiteaRequest RepoGetPullRequestFiles contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoGetPullRequestFiles contentType res accept
req GiteaRequest RepoGetPullRequestFiles contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetPullRequestFiles contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoGetPullRequestFiles MimeJSON
repoGetPullReview
:: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
repoGetPullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
repoGetPullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPullReview
instance Produces RepoGetPullReview MimeJSON
repoGetPullReviewComments
:: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoGetPullReviewComments MimeNoContent [PullReviewComment] MimeJSON
(Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/comments"]
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPullReviewComments
MimeNoContent
[PullReviewComment]
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data
instance Produces RepoGetPullReviewComments MimeJSON
repoGetPushMirrorByRemoteName
:: Owner
-> Repo
-> Name
-> GiteaRequest RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
repoGetPushMirrorByRemoteName :: Owner
-> Repo
-> Name
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
repoGetPushMirrorByRemoteName (Owner Text
owner) (Repo Text
repo) (Name Text
name) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetPushMirrorByRemoteName MimeNoContent PushMirror MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetPushMirrorByRemoteName
instance Produces RepoGetPushMirrorByRemoteName MimeJSON
repoGetRawFile
:: Owner
-> Repo
-> Filepath
-> GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
repoGetRawFile :: Owner
-> Repo
-> Filepath
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
repoGetRawFile (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/raw/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetRawFile MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetRawFile MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetRawFile
instance HasOptionalParam RepoGetRawFile Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetRawFile contentType res accept
-> Ref -> GiteaRequest RepoGetRawFile contentType res accept
applyOptionalParam GiteaRequest RepoGetRawFile contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoGetRawFile contentType res accept
req GiteaRequest RepoGetRawFile contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetRawFile contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetRawFile MimeOctetStream
repoGetRawFileOrLFS
:: Owner
-> Repo
-> Filepath
-> GiteaRequest RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
repoGetRawFileOrLFS :: Owner
-> Repo
-> Filepath
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
repoGetRawFileOrLFS (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/media/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetRawFileOrLFS MimeNoContent FilePath MimeOctetStream
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetRawFileOrLFS
instance HasOptionalParam RepoGetRawFileOrLFS Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetRawFileOrLFS contentType res accept
-> Ref -> GiteaRequest RepoGetRawFileOrLFS contentType res accept
applyOptionalParam GiteaRequest RepoGetRawFileOrLFS contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoGetRawFileOrLFS contentType res accept
req GiteaRequest RepoGetRawFileOrLFS contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetRawFileOrLFS contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoGetRawFileOrLFS MimeOctetStream
repoGetRelease
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
repoGetRelease :: Owner
-> Repo
-> Id
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
repoGetRelease (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetRelease MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetRelease
instance Produces RepoGetRelease MimeJSON
repoGetReleaseAttachment
:: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
repoGetReleaseAttachment :: Owner
-> Repo
-> Id
-> AttachmentId
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
repoGetReleaseAttachment (Owner Text
owner) (Repo Text
repo) (Id Integer
id) (AttachmentId Integer
attachmentId) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
attachmentId]
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetReleaseAttachment MimeNoContent Attachment MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetReleaseAttachment
instance Produces RepoGetReleaseAttachment MimeJSON
repoGetReleaseByTag
:: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
repoGetReleaseByTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
repoGetReleaseByTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
Method
-> [ByteString]
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetReleaseByTag MimeNoContent Release MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetReleaseByTag
instance Produces RepoGetReleaseByTag MimeJSON
repoGetRepoPermissions
:: Owner
-> Repo
-> Collaborator
-> GiteaRequest RepoGetRepoPermissions MimeNoContent RepoCollaboratorPermission MimeJSON
repoGetRepoPermissions :: Owner
-> Repo
-> Collaborator
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
repoGetRepoPermissions (Owner Text
owner) (Repo Text
repo) (Collaborator Text
collaborator) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
collaborator,ByteString
"/permission"]
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetRepoPermissions
MimeNoContent
RepoCollaboratorPermission
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetRepoPermissions
instance Produces RepoGetRepoPermissions MimeJSON
repoGetReviewers
:: Owner
-> Repo
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
repoGetReviewers :: Owner
-> Repo
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
repoGetReviewers (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/reviewers"]
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetReviewers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetReviewers
instance Produces RepoGetReviewers MimeJSON
repoGetRunnerRegistrationToken
:: Owner
-> Repo
-> GiteaRequest RepoGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
repoGetRunnerRegistrationToken :: Owner
-> Repo
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
repoGetRunnerRegistrationToken (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/runners/registration-token"]
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetRunnerRegistrationToken
instance Produces RepoGetRunnerRegistrationToken MimeNoContent
repoGetSingleCommit
:: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
repoGetSingleCommit :: Owner
-> Repo
-> Sha
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
repoGetSingleCommit (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetSingleCommit MimeNoContent Commit MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetSingleCommit
instance HasOptionalParam RepoGetSingleCommit Stat where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Stat -> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Stat Bool
xs) =
GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stat", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetSingleCommit Verification where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Verification
-> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Verification Bool
xs) =
GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"verification", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoGetSingleCommit Files where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetSingleCommit contentType res accept
-> Files -> GiteaRequest RepoGetSingleCommit contentType res accept
applyOptionalParam GiteaRequest RepoGetSingleCommit contentType res accept
req (Files Bool
xs) =
GiteaRequest RepoGetSingleCommit contentType res accept
req GiteaRequest RepoGetSingleCommit contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetSingleCommit contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"files", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces RepoGetSingleCommit MimeJSON
repoGetTag
:: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
repoGetTag :: Owner
-> Repo
-> Tag2
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
repoGetTag (Owner Text
owner) (Repo Text
repo) (Tag2 Text
tag) =
Method
-> [ByteString]
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
tag]
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetTag MimeNoContent Tag MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetTag
instance Produces RepoGetTag MimeJSON
repoGetTagProtection
:: Owner
-> Repo
-> IdInt
-> GiteaRequest RepoGetTagProtection MimeNoContent TagProtection MimeJSON
repoGetTagProtection :: Owner
-> Repo
-> IdInt
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
repoGetTagProtection (Owner Text
owner) (Repo Text
repo) (IdInt Int
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetTagProtection MimeNoContent TagProtection MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetTagProtection
instance Produces RepoGetTagProtection MimeJSON
repoGetWikiPage
:: Owner
-> Repo
-> PageName
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
repoGetWikiPage :: Owner
-> Repo
-> PageName
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
repoGetWikiPage (Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
Method
-> [ByteString]
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/page/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoGetWikiPage MimeNoContent WikiPage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetWikiPage
instance Produces RepoGetWikiPage MimeJSON
repoGetWikiPageRevisions
:: Owner
-> Repo
-> PageName
-> GiteaRequest RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
(Owner Text
owner) (Repo Text
repo) (PageName Text
pageName) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/revisions/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
pageName]
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetWikiPageRevisions MimeNoContent WikiCommitList MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data
instance HasOptionalParam RepoGetWikiPageRevisions Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPageRevisions contentType res accept
-> Page
-> GiteaRequest RepoGetWikiPageRevisions contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPageRevisions contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetWikiPageRevisions contentType res accept
req GiteaRequest RepoGetWikiPageRevisions contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPageRevisions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoGetWikiPageRevisions MimeJSON
repoGetWikiPages
:: Owner
-> Repo
-> GiteaRequest RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
repoGetWikiPages :: Owner
-> Repo
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
repoGetWikiPages (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/wiki/pages"]
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoGetWikiPages MimeNoContent [WikiPageMetaData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoGetWikiPages
instance HasOptionalParam RepoGetWikiPages Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPages contentType res accept
-> Page -> GiteaRequest RepoGetWikiPages contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPages contentType res accept
req (Page Int
xs) =
GiteaRequest RepoGetWikiPages contentType res accept
req GiteaRequest RepoGetWikiPages contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPages contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoGetWikiPages Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoGetWikiPages contentType res accept
-> Limit -> GiteaRequest RepoGetWikiPages contentType res accept
applyOptionalParam GiteaRequest RepoGetWikiPages contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoGetWikiPages contentType res accept
req GiteaRequest RepoGetWikiPages contentType res accept
-> [QueryItem]
-> GiteaRequest RepoGetWikiPages contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoGetWikiPages MimeJSON
repoListActionsSecrets
:: Owner
-> Repo
-> GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
repoListActionsSecrets :: Owner
-> Repo
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
repoListActionsSecrets (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets"]
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListActionsSecrets MimeNoContent [Secret] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListActionsSecrets
instance HasOptionalParam RepoListActionsSecrets Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActionsSecrets contentType res accept
-> Page
-> GiteaRequest RepoListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest RepoListActionsSecrets contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListActionsSecrets contentType res accept
req GiteaRequest RepoListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActionsSecrets contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListActionsSecrets Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActionsSecrets contentType res accept
-> Limit
-> GiteaRequest RepoListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest RepoListActionsSecrets contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListActionsSecrets contentType res accept
req GiteaRequest RepoListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActionsSecrets contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListActionsSecrets MimeJSON
repoListActivityFeeds
:: Owner
-> Repo
-> GiteaRequest RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
repoListActivityFeeds :: Owner
-> Repo
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
repoListActivityFeeds (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/activities/feeds"]
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListActivityFeeds
instance HasOptionalParam RepoListActivityFeeds ParamDate where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> ParamDate
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (ParamDate Date
xs) =
GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Date) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"date", Date -> Maybe Date
forall a. a -> Maybe a
Just Date
xs)
instance HasOptionalParam RepoListActivityFeeds Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> Page
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListActivityFeeds Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListActivityFeeds contentType res accept
-> Limit
-> GiteaRequest RepoListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest RepoListActivityFeeds contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListActivityFeeds contentType res accept
req GiteaRequest RepoListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListActivityFeeds MimeJSON
repoListAllGitRefs
:: Owner
-> Repo
-> GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
repoListAllGitRefs :: Owner
-> Repo
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
repoListAllGitRefs (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/refs"]
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListAllGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListAllGitRefs
instance Produces RepoListAllGitRefs MimeJSON
repoListBranchProtection
:: Owner
-> Repo
-> GiteaRequest RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
repoListBranchProtection :: Owner
-> Repo
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
repoListBranchProtection (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections"]
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListBranchProtection MimeNoContent [BranchProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListBranchProtection
instance Produces RepoListBranchProtection MimeJSON
repoListBranches
:: Owner
-> Repo
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
repoListBranches :: Owner
-> Repo
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
repoListBranches (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches"]
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListBranches MimeNoContent [Branch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListBranches
instance HasOptionalParam RepoListBranches Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListBranches contentType res accept
-> Page -> GiteaRequest RepoListBranches contentType res accept
applyOptionalParam GiteaRequest RepoListBranches contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListBranches contentType res accept
req GiteaRequest RepoListBranches contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListBranches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListBranches Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListBranches contentType res accept
-> Limit -> GiteaRequest RepoListBranches contentType res accept
applyOptionalParam GiteaRequest RepoListBranches contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListBranches contentType res accept
req GiteaRequest RepoListBranches contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListBranches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListBranches MimeJSON
repoListCollaborators
:: Owner
-> Repo
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
repoListCollaborators :: Owner
-> Repo
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
repoListCollaborators (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/collaborators"]
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListCollaborators MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListCollaborators
instance HasOptionalParam RepoListCollaborators Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListCollaborators contentType res accept
-> Page
-> GiteaRequest RepoListCollaborators contentType res accept
applyOptionalParam GiteaRequest RepoListCollaborators contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListCollaborators contentType res accept
req GiteaRequest RepoListCollaborators contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListCollaborators contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListCollaborators Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListCollaborators contentType res accept
-> Limit
-> GiteaRequest RepoListCollaborators contentType res accept
applyOptionalParam GiteaRequest RepoListCollaborators contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListCollaborators contentType res accept
req GiteaRequest RepoListCollaborators contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListCollaborators contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListCollaborators MimeJSON
repoListGitHooks
:: Owner
-> Repo
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
repoListGitHooks :: Owner
-> Repo
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
repoListGitHooks (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/git"]
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListGitHooks MimeNoContent [GitHook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListGitHooks
instance Produces RepoListGitHooks MimeJSON
repoListGitRefs
:: Owner
-> Repo
-> Ref
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
repoListGitRefs :: Owner
-> Repo
-> Ref
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
repoListGitRefs (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
Method
-> [ByteString]
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/git/refs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref]
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListGitRefs MimeNoContent [Reference] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListGitRefs
instance Produces RepoListGitRefs MimeJSON
repoListHooks
:: Owner
-> Repo
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
repoListHooks :: Owner
-> Repo -> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
repoListHooks (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks"]
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListHooks MimeNoContent [Hook] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListHooks
instance HasOptionalParam RepoListHooks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListHooks contentType res accept
-> Page -> GiteaRequest RepoListHooks contentType res accept
applyOptionalParam GiteaRequest RepoListHooks contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListHooks contentType res accept
req GiteaRequest RepoListHooks contentType res accept
-> [QueryItem] -> GiteaRequest RepoListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListHooks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListHooks contentType res accept
-> Limit -> GiteaRequest RepoListHooks contentType res accept
applyOptionalParam GiteaRequest RepoListHooks contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListHooks contentType res accept
req GiteaRequest RepoListHooks contentType res accept
-> [QueryItem] -> GiteaRequest RepoListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListHooks MimeJSON
repoListKeys
:: Owner
-> Repo
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
repoListKeys :: Owner
-> Repo
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
repoListKeys (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/keys"]
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListKeys MimeNoContent [DeployKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListKeys
instance HasOptionalParam RepoListKeys KeyId where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> KeyId -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (KeyId Int
xs) =
GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"key_id", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListKeys Fingerprint where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Fingerprint -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Fingerprint Text
xs) =
GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fingerprint", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoListKeys Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Page -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListKeys Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListKeys contentType res accept
-> Limit -> GiteaRequest RepoListKeys contentType res accept
applyOptionalParam GiteaRequest RepoListKeys contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListKeys contentType res accept
req GiteaRequest RepoListKeys contentType res accept
-> [QueryItem] -> GiteaRequest RepoListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListKeys MimeJSON
repoListPinnedIssues
:: Owner
-> Repo
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
repoListPinnedIssues :: Owner
-> Repo
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
repoListPinnedIssues (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issues/pinned"]
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListPinnedIssues MimeNoContent [Issue] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListPinnedIssues
instance Produces RepoListPinnedIssues MimeJSON
repoListPinnedPullRequests
:: Owner
-> Repo
-> GiteaRequest RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPinnedPullRequests :: Owner
-> Repo
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPinnedPullRequests (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/pinned"]
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListPinnedPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListPinnedPullRequests
instance Produces RepoListPinnedPullRequests MimeJSON
repoListPullRequests
:: Owner
-> Repo
-> GiteaRequest RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPullRequests :: Owner
-> Repo
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
repoListPullRequests (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls"]
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListPullRequests MimeNoContent [PullRequest] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListPullRequests
instance HasOptionalParam RepoListPullRequests State where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> State
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (State E'State2
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State2) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State2 -> Maybe E'State2
forall a. a -> Maybe a
Just E'State2
xs)
instance HasOptionalParam RepoListPullRequests Sort3 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Sort3
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Sort3 E'Sort2
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort2) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort2 -> Maybe E'Sort2
forall a. a -> Maybe a
Just E'Sort2
xs)
instance HasOptionalParam RepoListPullRequests Milestone2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Milestone2
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Milestone2 Integer
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"milestone", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam RepoListPullRequests LabelsInteger where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> LabelsInteger
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (LabelsInteger [Integer]
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Integer]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"labels", [Integer] -> Maybe [Integer]
forall a. a -> Maybe a
Just [Integer]
xs)
instance HasOptionalParam RepoListPullRequests Poster where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Poster
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Poster Text
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"poster", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoListPullRequests Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Page -> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListPullRequests Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullRequests contentType res accept
-> Limit
-> GiteaRequest RepoListPullRequests contentType res accept
applyOptionalParam GiteaRequest RepoListPullRequests contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListPullRequests contentType res accept
req GiteaRequest RepoListPullRequests contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullRequests contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListPullRequests MimeJSON
repoListPullReviews
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoListPullReviews MimeNoContent [PullReview] MimeJSON
repoListPullReviews :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
repoListPullReviews (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews"]
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListPullReviews MimeNoContent [PullReview] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListPullReviews
instance HasOptionalParam RepoListPullReviews Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullReviews contentType res accept
-> Page -> GiteaRequest RepoListPullReviews contentType res accept
applyOptionalParam GiteaRequest RepoListPullReviews contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListPullReviews contentType res accept
req GiteaRequest RepoListPullReviews contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullReviews contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListPullReviews Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPullReviews contentType res accept
-> Limit -> GiteaRequest RepoListPullReviews contentType res accept
applyOptionalParam GiteaRequest RepoListPullReviews contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListPullReviews contentType res accept
req GiteaRequest RepoListPullReviews contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPullReviews contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListPullReviews MimeJSON
repoListPushMirrors
:: Owner
-> Repo
-> GiteaRequest RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
repoListPushMirrors :: Owner
-> Repo
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
repoListPushMirrors (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors"]
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListPushMirrors MimeNoContent [PushMirror] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListPushMirrors
instance HasOptionalParam RepoListPushMirrors Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPushMirrors contentType res accept
-> Page -> GiteaRequest RepoListPushMirrors contentType res accept
applyOptionalParam GiteaRequest RepoListPushMirrors contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListPushMirrors contentType res accept
req GiteaRequest RepoListPushMirrors contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPushMirrors contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListPushMirrors Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListPushMirrors contentType res accept
-> Limit -> GiteaRequest RepoListPushMirrors contentType res accept
applyOptionalParam GiteaRequest RepoListPushMirrors contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListPushMirrors contentType res accept
req GiteaRequest RepoListPushMirrors contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListPushMirrors contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListPushMirrors MimeJSON
repoListReleaseAttachments
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
repoListReleaseAttachments :: Owner
-> Repo
-> Id
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
repoListReleaseAttachments (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/assets"]
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListReleaseAttachments MimeNoContent [Attachment] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListReleaseAttachments
instance Produces RepoListReleaseAttachments MimeJSON
repoListReleases
:: Owner
-> Repo
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
repoListReleases :: Owner
-> Repo
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
repoListReleases (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/releases"]
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListReleases MimeNoContent [Release] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListReleases
instance HasOptionalParam RepoListReleases Draft where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Draft -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Draft Bool
xs) =
GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"draft", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoListReleases PreRelease where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> PreRelease
-> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (PreRelease Bool
xs) =
GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pre-release", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoListReleases Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Page -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListReleases Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListReleases contentType res accept
-> Limit -> GiteaRequest RepoListReleases contentType res accept
applyOptionalParam GiteaRequest RepoListReleases contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListReleases contentType res accept
req GiteaRequest RepoListReleases contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListReleases contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListReleases MimeJSON
repoListStargazers
:: Owner
-> Repo
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
repoListStargazers :: Owner
-> Repo
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
repoListStargazers (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/stargazers"]
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListStargazers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListStargazers
instance HasOptionalParam RepoListStargazers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStargazers contentType res accept
-> Page -> GiteaRequest RepoListStargazers contentType res accept
applyOptionalParam GiteaRequest RepoListStargazers contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListStargazers contentType res accept
req GiteaRequest RepoListStargazers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStargazers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListStargazers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStargazers contentType res accept
-> Limit -> GiteaRequest RepoListStargazers contentType res accept
applyOptionalParam GiteaRequest RepoListStargazers contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListStargazers contentType res accept
req GiteaRequest RepoListStargazers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStargazers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListStargazers MimeJSON
repoListStatuses
:: Owner
-> Repo
-> Sha
-> GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
repoListStatuses :: Owner
-> Repo
-> Sha
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
repoListStatuses (Owner Text
owner) (Repo Text
repo) (Sha Text
sha) =
Method
-> [ByteString]
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/statuses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
sha]
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListStatuses MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListStatuses
instance HasOptionalParam RepoListStatuses Sort2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Sort2 -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Sort2 E'Sort
xs) =
GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort -> Maybe E'Sort
forall a. a -> Maybe a
Just E'Sort
xs)
instance HasOptionalParam RepoListStatuses State2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> State2 -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (State2 E'State3
xs) =
GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State3 -> Maybe E'State3
forall a. a -> Maybe a
Just E'State3
xs)
instance HasOptionalParam RepoListStatuses Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Page -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListStatuses Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatuses contentType res accept
-> Limit -> GiteaRequest RepoListStatuses contentType res accept
applyOptionalParam GiteaRequest RepoListStatuses contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListStatuses contentType res accept
req GiteaRequest RepoListStatuses contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatuses contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListStatuses MimeJSON
repoListStatusesByRef
:: Owner
-> Repo
-> Ref
-> GiteaRequest RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
repoListStatusesByRef :: Owner
-> Repo
-> Ref
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
repoListStatusesByRef (Owner Text
owner) (Repo Text
repo) (Ref Text
ref) =
Method
-> [ByteString]
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/commits/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
ref,ByteString
"/statuses"]
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListStatusesByRef MimeNoContent [CommitStatus] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListStatusesByRef
instance HasOptionalParam RepoListStatusesByRef Sort2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Sort2
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Sort2 E'Sort
xs) =
GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Sort) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", E'Sort -> Maybe E'Sort
forall a. a -> Maybe a
Just E'Sort
xs)
instance HasOptionalParam RepoListStatusesByRef State2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> State2
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (State2 E'State3
xs) =
GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'State3) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"state", E'State3 -> Maybe E'State3
forall a. a -> Maybe a
Just E'State3
xs)
instance HasOptionalParam RepoListStatusesByRef Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Page
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListStatusesByRef Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListStatusesByRef contentType res accept
-> Limit
-> GiteaRequest RepoListStatusesByRef contentType res accept
applyOptionalParam GiteaRequest RepoListStatusesByRef contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListStatusesByRef contentType res accept
req GiteaRequest RepoListStatusesByRef contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListStatusesByRef contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListStatusesByRef MimeJSON
repoListSubscribers
:: Owner
-> Repo
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
repoListSubscribers :: Owner
-> Repo
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
repoListSubscribers (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscribers"]
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListSubscribers MimeNoContent [User] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListSubscribers
instance HasOptionalParam RepoListSubscribers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListSubscribers contentType res accept
-> Page -> GiteaRequest RepoListSubscribers contentType res accept
applyOptionalParam GiteaRequest RepoListSubscribers contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListSubscribers contentType res accept
req GiteaRequest RepoListSubscribers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListSubscribers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListSubscribers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListSubscribers contentType res accept
-> Limit -> GiteaRequest RepoListSubscribers contentType res accept
applyOptionalParam GiteaRequest RepoListSubscribers contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListSubscribers contentType res accept
req GiteaRequest RepoListSubscribers contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListSubscribers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListSubscribers MimeJSON
repoListTagProtection
:: Owner
-> Repo
-> GiteaRequest RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
repoListTagProtection :: Owner
-> Repo
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
repoListTagProtection (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tag_protections"]
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoListTagProtection MimeNoContent [TagProtection] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListTagProtection
instance Produces RepoListTagProtection MimeJSON
repoListTags
:: Owner
-> Repo
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
repoListTags :: Owner
-> Repo -> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
repoListTags (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/tags"]
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTags MimeNoContent [Tag] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListTags
instance HasOptionalParam RepoListTags Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTags contentType res accept
-> Page -> GiteaRequest RepoListTags contentType res accept
applyOptionalParam GiteaRequest RepoListTags contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListTags contentType res accept
req GiteaRequest RepoListTags contentType res accept
-> [QueryItem] -> GiteaRequest RepoListTags contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListTags Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTags contentType res accept
-> Limit -> GiteaRequest RepoListTags contentType res accept
applyOptionalParam GiteaRequest RepoListTags contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListTags contentType res accept
req GiteaRequest RepoListTags contentType res accept
-> [QueryItem] -> GiteaRequest RepoListTags contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListTags MimeJSON
repoListTeams
:: Owner
-> Repo
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
repoListTeams :: Owner
-> Repo -> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
repoListTeams (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/teams"]
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListTeams
instance Produces RepoListTeams MimeJSON
repoListTopics
:: Owner
-> Repo
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
repoListTopics :: Owner
-> Repo
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
repoListTopics (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics"]
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoListTopics MimeNoContent TopicName MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoListTopics
instance HasOptionalParam RepoListTopics Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTopics contentType res accept
-> Page -> GiteaRequest RepoListTopics contentType res accept
applyOptionalParam GiteaRequest RepoListTopics contentType res accept
req (Page Int
xs) =
GiteaRequest RepoListTopics contentType res accept
req GiteaRequest RepoListTopics contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListTopics contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoListTopics Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoListTopics contentType res accept
-> Limit -> GiteaRequest RepoListTopics contentType res accept
applyOptionalParam GiteaRequest RepoListTopics contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoListTopics contentType res accept
req GiteaRequest RepoListTopics contentType res accept
-> [QueryItem]
-> GiteaRequest RepoListTopics contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoListTopics MimeJSON
repoMergePullRequest
:: (Consumes RepoMergePullRequest contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Index
-> GiteaRequest RepoMergePullRequest contentType NoContent MimeNoContent
repoMergePullRequest :: forall contentType.
Consumes RepoMergePullRequest contentType =>
ContentType contentType
-> Owner
-> Repo
-> Index
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
repoMergePullRequest ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoMergePullRequest contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoMergePullRequest
instance HasBodyParam RepoMergePullRequest MergePullRequestOption
instance Consumes RepoMergePullRequest MimeJSON
instance Consumes RepoMergePullRequest MimePlainText
instance Produces RepoMergePullRequest MimeNoContent
repoMergeUpstream
:: (Consumes RepoMergeUpstream contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
repoMergeUpstream :: forall contentType.
Consumes RepoMergeUpstream contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
repoMergeUpstream ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/merge-upstream"]
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoMergeUpstream contentType MergeUpstreamResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoMergeUpstream
instance HasBodyParam RepoMergeUpstream MergeUpstreamRequest
instance Consumes RepoMergeUpstream MimeJSON
instance Consumes RepoMergeUpstream MimePlainText
instance Produces RepoMergeUpstream MimeJSON
repoMigrate
:: (Consumes RepoMigrate MimeJSON)
=> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
repoMigrate :: Consumes RepoMigrate MimeJSON =>
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
repoMigrate =
Method
-> [ByteString]
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/migrate"]
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoMigrate MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoMigrate
instance HasBodyParam RepoMigrate MigrateRepoOptions
instance Consumes RepoMigrate MimeJSON
instance Produces RepoMigrate MimeJSON
repoMirrorSync
:: Owner
-> Repo
-> GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
repoMirrorSync :: Owner
-> Repo
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
repoMirrorSync (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/mirror-sync"]
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoMirrorSync
instance Produces RepoMirrorSync MimeNoContent
repoNewPinAllowed
:: Owner
-> Repo
-> GiteaRequest RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
repoNewPinAllowed :: Owner
-> Repo
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
repoNewPinAllowed (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/new_pin_allowed"]
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoNewPinAllowed MimeNoContent NewIssuePinsAllowed MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoNewPinAllowed
instance Produces RepoNewPinAllowed MimeJSON
repoPullRequestIsMerged
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
repoPullRequestIsMerged :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
repoPullRequestIsMerged (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/merge"]
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoPullRequestIsMerged MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoPullRequestIsMerged
instance Produces RepoPullRequestIsMerged MimeNoContent
repoPushMirrorSync
:: Owner
-> Repo
-> GiteaRequest RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
repoPushMirrorSync :: Owner
-> Repo
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
repoPushMirrorSync (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/push_mirrors-sync"]
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoPushMirrorSync MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoPushMirrorSync
instance Produces RepoPushMirrorSync MimeNoContent
repoSearch
:: GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
repoSearch :: GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
repoSearch =
Method
-> [ByteString]
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/search"]
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoSearch MimeNoContent SearchResults MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoSearch
instance HasOptionalParam RepoSearch Q where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Q -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Q Text
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"q", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoSearch Topic where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Topic -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Topic Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"topic", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch IncludeDesc where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> IncludeDesc -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (IncludeDesc Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"includeDesc", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch Uid where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Uid -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Uid Integer
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"uid", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam RepoSearch PriorityOwnerId where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> PriorityOwnerId
-> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (PriorityOwnerId Integer
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"priority_owner_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam RepoSearch TeamId where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> TeamId -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (TeamId Integer
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"team_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam RepoSearch StarredBy where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> StarredBy -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (StarredBy Integer
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"starredBy", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam RepoSearch Private where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Private -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Private Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"private", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch IsPrivate where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> IsPrivate -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (IsPrivate Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"is_private", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch Template where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Template -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Template Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"template", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch Archived where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Archived -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Archived Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"archived", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch Mode where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Mode -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Mode Text
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"mode", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoSearch Exclusive where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Exclusive -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Exclusive Bool
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"exclusive", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam RepoSearch Sort where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Sort -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Sort Text
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sort", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoSearch Order where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Order -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Order Text
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"order", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoSearch Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Page -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Page Int
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoSearch Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoSearch contentType res accept
-> Limit -> GiteaRequest RepoSearch contentType res accept
applyOptionalParam GiteaRequest RepoSearch contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoSearch contentType res accept
req GiteaRequest RepoSearch contentType res accept
-> [QueryItem] -> GiteaRequest RepoSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoSearch MimeJSON
repoSigningKey
:: Owner
-> Repo
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
repoSigningKey :: Owner
-> Repo
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
repoSigningKey (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/signing-key.gpg"]
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoSigningKey MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoSigningKey
instance Produces RepoSigningKey MimePlainText
repoSubmitPullReview
:: (Consumes RepoSubmitPullReview contentType, MimeRender contentType SubmitPullReviewOptions)
=> ContentType contentType
-> SubmitPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
repoSubmitPullReview :: forall contentType.
(Consumes RepoSubmitPullReview contentType,
MimeRender contentType SubmitPullReviewOptions) =>
ContentType contentType
-> SubmitPullReviewOptions
-> Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
repoSubmitPullReview ContentType contentType
_ SubmitPullReviewOptions
body (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoSubmitPullReview contentType PullReview MimeJSON
-> SubmitPullReviewOptions
-> GiteaRequest
RepoSubmitPullReview contentType PullReview MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoSubmitPullReview contentType,
MimeRender contentType SubmitPullReviewOptions) =>
GiteaRequest RepoSubmitPullReview contentType res accept
-> SubmitPullReviewOptions
-> GiteaRequest RepoSubmitPullReview contentType res accept
`setBodyParam` SubmitPullReviewOptions
body
data RepoSubmitPullReview
instance HasBodyParam RepoSubmitPullReview SubmitPullReviewOptions
instance Consumes RepoSubmitPullReview MimeJSON
instance Consumes RepoSubmitPullReview MimePlainText
instance Produces RepoSubmitPullReview MimeJSON
repoTestHook
:: Owner
-> Repo
-> Id
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
repoTestHook :: Owner
-> Repo
-> Id
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
repoTestHook (Owner Text
owner) (Repo Text
repo) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/tests"]
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoTestHook MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoTestHook
instance HasOptionalParam RepoTestHook Ref where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTestHook contentType res accept
-> Ref -> GiteaRequest RepoTestHook contentType res accept
applyOptionalParam GiteaRequest RepoTestHook contentType res accept
req (Ref Text
xs) =
GiteaRequest RepoTestHook contentType res accept
req GiteaRequest RepoTestHook contentType res accept
-> [QueryItem] -> GiteaRequest RepoTestHook contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ref", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces RepoTestHook MimeNoContent
repoTrackedTimes
:: Owner
-> Repo
-> GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
repoTrackedTimes :: Owner
-> Repo
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
repoTrackedTimes (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/times"]
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoTrackedTimes
instance HasOptionalParam RepoTrackedTimes User2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> User2 -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (User2 Text
xs) =
GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"user", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam RepoTrackedTimes Since where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Since -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Since DateTime
xs) =
GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"since", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam RepoTrackedTimes Before where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Before -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Before DateTime
xs) =
GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"before", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam RepoTrackedTimes Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Page -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Page Int
xs) =
GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam RepoTrackedTimes Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoTrackedTimes contentType res accept
-> Limit -> GiteaRequest RepoTrackedTimes contentType res accept
applyOptionalParam GiteaRequest RepoTrackedTimes contentType res accept
req (Limit Int
xs) =
GiteaRequest RepoTrackedTimes contentType res accept
req GiteaRequest RepoTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest RepoTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces RepoTrackedTimes MimeJSON
repoTransfer0
:: (Consumes RepoTransfer0 contentType, MimeRender contentType TransferRepoOption)
=> ContentType contentType
-> TransferRepoOption
-> Owner
-> Repo
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
repoTransfer0 :: forall contentType.
(Consumes RepoTransfer0 contentType,
MimeRender contentType TransferRepoOption) =>
ContentType contentType
-> TransferRepoOption
-> Owner
-> Repo
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
repoTransfer0 ContentType contentType
_ TransferRepoOption
body (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/transfer"]
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoTransfer0 contentType Repository MimeJSON
-> TransferRepoOption
-> GiteaRequest RepoTransfer0 contentType Repository MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoTransfer0 contentType,
MimeRender contentType TransferRepoOption) =>
GiteaRequest RepoTransfer0 contentType res accept
-> TransferRepoOption
-> GiteaRequest RepoTransfer0 contentType res accept
`setBodyParam` TransferRepoOption
body
data RepoTransfer0
instance HasBodyParam RepoTransfer0 TransferRepoOption
instance Consumes RepoTransfer0 MimeJSON
instance Consumes RepoTransfer0 MimePlainText
instance Produces RepoTransfer0 MimeJSON
repoUnDismissPullReview
:: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
repoUnDismissPullReview :: Owner
-> Repo
-> Index
-> Id
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
repoUnDismissPullReview (Owner Text
owner) (Repo Text
repo) (Index Integer
index) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/reviews/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/undismissals"]
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoUnDismissPullReview MimeNoContent PullReview MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUnDismissPullReview
instance Produces RepoUnDismissPullReview MimeJSON
repoUpdateAvatar
:: (Consumes RepoUpdateAvatar contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
repoUpdateAvatar :: forall contentType.
Consumes RepoUpdateAvatar contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
repoUpdateAvatar ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/avatar"]
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoUpdateAvatar contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUpdateAvatar
instance HasBodyParam RepoUpdateAvatar UpdateRepoAvatarOption
instance Consumes RepoUpdateAvatar MimeJSON
instance Consumes RepoUpdateAvatar MimePlainText
instance Produces RepoUpdateAvatar MimeNoContent
repoUpdateBranch
:: (Consumes RepoUpdateBranch MimeJSON)
=> Owner
-> Repo
-> Branch2
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
repoUpdateBranch :: Consumes RepoUpdateBranch MimeJSON =>
Owner
-> Repo
-> Branch2
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
repoUpdateBranch (Owner Text
owner) (Repo Text
repo) (Branch2 Text
branch) =
Method
-> [ByteString]
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branches/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
branch]
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoUpdateBranch MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUpdateBranch
instance HasBodyParam RepoUpdateBranch UpdateBranchRepoOption
instance Consumes RepoUpdateBranch MimeJSON
instance Produces RepoUpdateBranch MimeNoContent
repoUpdateBranchProtectionPriories
:: (Consumes RepoUpdateBranchProtectionPriories MimeJSON)
=> Owner
-> Repo
-> GiteaRequest RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
repoUpdateBranchProtectionPriories :: Consumes RepoUpdateBranchProtectionPriories MimeJSON =>
Owner
-> Repo
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
repoUpdateBranchProtectionPriories (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/branch_protections/priority"]
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoUpdateBranchProtectionPriories MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUpdateBranchProtectionPriories
instance HasBodyParam RepoUpdateBranchProtectionPriories UpdateBranchProtectionPriories
instance Consumes RepoUpdateBranchProtectionPriories MimeJSON
instance Produces RepoUpdateBranchProtectionPriories MimeNoContent
repoUpdateFile
:: (Consumes RepoUpdateFile MimeJSON, MimeRender MimeJSON UpdateFileOptions)
=> UpdateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
repoUpdateFile :: (Consumes RepoUpdateFile MimeJSON,
MimeRender MimeJSON UpdateFileOptions) =>
UpdateFileOptions
-> Owner
-> Repo
-> Filepath
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
repoUpdateFile UpdateFileOptions
body (Owner Text
owner) (Repo Text
repo) (Filepath Text
filepath) =
Method
-> [ByteString]
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/contents/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
filepath]
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
-> UpdateFileOptions
-> GiteaRequest RepoUpdateFile MimeJSON FileResponse MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes RepoUpdateFile contentType,
MimeRender contentType UpdateFileOptions) =>
GiteaRequest RepoUpdateFile contentType res accept
-> UpdateFileOptions
-> GiteaRequest RepoUpdateFile contentType res accept
`setBodyParam` UpdateFileOptions
body
data RepoUpdateFile
instance HasBodyParam RepoUpdateFile UpdateFileOptions
instance Consumes RepoUpdateFile MimeJSON
instance Produces RepoUpdateFile MimeJSON
repoUpdatePullRequest
:: Owner
-> Repo
-> Index
-> GiteaRequest RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
repoUpdatePullRequest :: Owner
-> Repo
-> Index
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
repoUpdatePullRequest (Owner Text
owner) (Repo Text
repo) (Index Integer
index) =
Method
-> [ByteString]
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/pulls/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
index,ByteString
"/update"]
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoUpdatePullRequest MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUpdatePullRequest
instance HasOptionalParam RepoUpdatePullRequest Style where
applyOptionalParam :: forall contentType res accept.
GiteaRequest RepoUpdatePullRequest contentType res accept
-> Style
-> GiteaRequest RepoUpdatePullRequest contentType res accept
applyOptionalParam GiteaRequest RepoUpdatePullRequest contentType res accept
req (Style E'Style
xs) =
GiteaRequest RepoUpdatePullRequest contentType res accept
req GiteaRequest RepoUpdatePullRequest contentType res accept
-> [QueryItem]
-> GiteaRequest RepoUpdatePullRequest contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe E'Style) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"style", E'Style -> Maybe E'Style
forall a. a -> Maybe a
Just E'Style
xs)
instance Produces RepoUpdatePullRequest MimeNoContent
repoUpdateTopics
:: (Consumes RepoUpdateTopics contentType)
=> ContentType contentType
-> Owner
-> Repo
-> GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
repoUpdateTopics :: forall contentType.
Consumes RepoUpdateTopics contentType =>
ContentType contentType
-> Owner
-> Repo
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
repoUpdateTopics ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/topics"]
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest RepoUpdateTopics contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoUpdateTopics contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoUpdateTopics
instance HasBodyParam RepoUpdateTopics RepoTopicOptions
instance Consumes RepoUpdateTopics MimeJSON
instance Consumes RepoUpdateTopics MimePlainText
instance Produces RepoUpdateTopics MimeNoContent
repoValidateIssueConfig
:: Owner
-> Repo
-> GiteaRequest RepoValidateIssueConfig MimeNoContent IssueConfigValidation MimeJSON
repoValidateIssueConfig :: Owner
-> Repo
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
repoValidateIssueConfig (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/issue_config/validate"]
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
RepoValidateIssueConfig
MimeNoContent
IssueConfigValidation
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data RepoValidateIssueConfig
instance Produces RepoValidateIssueConfig MimeJSON
topicSearch
:: Q
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
topicSearch :: Q
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
topicSearch (Q Text
q) =
Method
-> [ByteString]
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/topics/search"]
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
-> [QueryItem]
-> GiteaRequest TopicSearch MimeNoContent [TopicResponse] MimeJSON
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"q", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
q)
data TopicSearch
instance HasOptionalParam TopicSearch Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TopicSearch contentType res accept
-> Page -> GiteaRequest TopicSearch contentType res accept
applyOptionalParam GiteaRequest TopicSearch contentType res accept
req (Page Int
xs) =
GiteaRequest TopicSearch contentType res accept
req GiteaRequest TopicSearch contentType res accept
-> [QueryItem] -> GiteaRequest TopicSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam TopicSearch Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TopicSearch contentType res accept
-> Limit -> GiteaRequest TopicSearch contentType res accept
applyOptionalParam GiteaRequest TopicSearch contentType res accept
req (Limit Int
xs) =
GiteaRequest TopicSearch contentType res accept
req GiteaRequest TopicSearch contentType res accept
-> [QueryItem] -> GiteaRequest TopicSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces TopicSearch MimeJSON
updateRepoSecret
:: (Consumes UpdateRepoSecret MimeJSON)
=> Owner
-> Repo
-> Secretname
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
updateRepoSecret :: Consumes UpdateRepoSecret MimeJSON =>
Owner
-> Repo
-> Secretname
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
updateRepoSecret (Owner Text
owner) (Repo Text
repo) (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateRepoSecret MimeJSON NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UpdateRepoSecret
instance HasBodyParam UpdateRepoSecret CreateOrUpdateSecretOption
instance Consumes UpdateRepoSecret MimeJSON
instance Produces UpdateRepoSecret MimeNoContent
updateRepoVariable
:: (Consumes UpdateRepoVariable contentType)
=> ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
updateRepoVariable :: forall contentType.
Consumes UpdateRepoVariable contentType =>
ContentType contentType
-> Owner
-> Repo
-> Variablename
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
updateRepoVariable ContentType contentType
_ (Owner Text
owner) (Repo Text
repo) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UpdateRepoVariable contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UpdateRepoVariable contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UpdateRepoVariable
instance HasBodyParam UpdateRepoVariable UpdateVariableOption
instance Consumes UpdateRepoVariable MimeJSON
instance Consumes UpdateRepoVariable MimePlainText
instance Produces UpdateRepoVariable MimeNoContent
userCurrentCheckSubscription
:: Accept accept
-> Owner
-> Repo
-> GiteaRequest UserCurrentCheckSubscription MimeNoContent WatchInfo accept
userCurrentCheckSubscription :: forall accept.
Accept accept
-> Owner
-> Repo
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
userCurrentCheckSubscription Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentCheckSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentCheckSubscription
instance Produces UserCurrentCheckSubscription MimeTextHtml
instance Produces UserCurrentCheckSubscription MimeJSON
userCurrentDeleteSubscription
:: Owner
-> Repo
-> GiteaRequest UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
userCurrentDeleteSubscription :: Owner
-> Repo
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
userCurrentDeleteSubscription (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentDeleteSubscription MimeNoContent NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentDeleteSubscription
instance Produces UserCurrentDeleteSubscription MimeNoContent
userCurrentPutSubscription
:: Accept accept
-> Owner
-> Repo
-> GiteaRequest UserCurrentPutSubscription MimeNoContent WatchInfo accept
userCurrentPutSubscription :: forall accept.
Accept accept
-> Owner
-> Repo
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
userCurrentPutSubscription Accept accept
_ (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/subscription"]
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentPutSubscription MimeNoContent WatchInfo accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentPutSubscription
instance Produces UserCurrentPutSubscription MimeTextHtml
instance Produces UserCurrentPutSubscription MimeJSON
userTrackedTimes
:: Owner
-> Repo
-> User2
-> GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userTrackedTimes :: Owner
-> Repo
-> User2
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userTrackedTimes (Owner Text
owner) (Repo Text
repo) (User2 Text
user) =
Method
-> [ByteString]
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/times/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
user]
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
{-# DEPRECATED userTrackedTimes "" #-}
data UserTrackedTimes
instance Produces UserTrackedTimes MimeJSON