{-# 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.Organization 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
createOrgRepo
:: (Consumes CreateOrgRepo MimeJSON)
=> Org
-> GiteaRequest CreateOrgRepo MimeJSON Repository MimeJSON
createOrgRepo :: Consumes CreateOrgRepo MimeJSON =>
Org -> GiteaRequest CreateOrgRepo MimeJSON Repository MimeJSON
createOrgRepo (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest CreateOrgRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/repos"]
GiteaRequest CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateOrgRepo 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 CreateOrgRepo
instance HasBodyParam CreateOrgRepo CreateRepoOption
instance Consumes CreateOrgRepo MimeJSON
instance Produces CreateOrgRepo MimeJSON
createOrgRepoDeprecated
:: (Consumes CreateOrgRepoDeprecated MimeJSON)
=> Org
-> GiteaRequest CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
createOrgRepoDeprecated :: Consumes CreateOrgRepoDeprecated MimeJSON =>
Org
-> GiteaRequest
CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
createOrgRepoDeprecated (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/org/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/repos"]
GiteaRequest CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
CreateOrgRepoDeprecated 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 CreateOrgRepoDeprecated MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
CreateOrgRepoDeprecated 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)
{-# DEPRECATED createOrgRepoDeprecated "" #-}
data CreateOrgRepoDeprecated
instance HasBodyParam CreateOrgRepoDeprecated CreateRepoOption
instance Consumes CreateOrgRepoDeprecated MimeJSON
instance Produces CreateOrgRepoDeprecated MimeJSON
createOrgVariable
:: (Consumes CreateOrgVariable MimeJSON)
=> Org
-> Variablename
-> GiteaRequest CreateOrgVariable MimeJSON NoContent MimeNoContent
createOrgVariable :: Consumes CreateOrgVariable MimeJSON =>
Org
-> Variablename
-> GiteaRequest CreateOrgVariable MimeJSON NoContent MimeNoContent
createOrgVariable (Org Text
org) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest CreateOrgVariable MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateOrgVariable 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 CreateOrgVariable
instance HasBodyParam CreateOrgVariable CreateVariableOption
instance Consumes CreateOrgVariable MimeJSON
instance Produces CreateOrgVariable MimeNoContent
deleteOrgSecret
:: Org
-> Secretname
-> GiteaRequest DeleteOrgSecret MimeNoContent NoContent MimeNoContent
deleteOrgSecret :: Org
-> Secretname
-> GiteaRequest
DeleteOrgSecret MimeNoContent NoContent MimeNoContent
deleteOrgSecret (Org Text
org) (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest
DeleteOrgSecret MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteOrgSecret MimeNoContent 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 DeleteOrgSecret
instance Produces DeleteOrgSecret MimeNoContent
deleteOrgVariable
:: Org
-> Variablename
-> GiteaRequest DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
deleteOrgVariable :: Org
-> Variablename
-> GiteaRequest
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
deleteOrgVariable (Org Text
org) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteOrgVariable 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
DeleteOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteOrgVariable 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 DeleteOrgVariable
instance Produces DeleteOrgVariable MimeJSON
getOrgVariable
:: Org
-> Variablename
-> GiteaRequest GetOrgVariable MimeNoContent ActionVariable MimeJSON
getOrgVariable :: Org
-> Variablename
-> GiteaRequest
GetOrgVariable MimeNoContent ActionVariable MimeJSON
getOrgVariable (Org Text
org) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
GetOrgVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetOrgVariable 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 GetOrgVariable
instance Produces GetOrgVariable MimeJSON
getOrgVariablesList
:: Org
-> GiteaRequest GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
getOrgVariablesList :: Org
-> GiteaRequest
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
getOrgVariablesList (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/variables"]
GiteaRequest
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetOrgVariablesList 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
GetOrgVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetOrgVariablesList 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 GetOrgVariablesList
instance HasOptionalParam GetOrgVariablesList Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetOrgVariablesList contentType res accept
-> Page -> GiteaRequest GetOrgVariablesList contentType res accept
applyOptionalParam GiteaRequest GetOrgVariablesList contentType res accept
req (Page Int
xs) =
GiteaRequest GetOrgVariablesList contentType res accept
req GiteaRequest GetOrgVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetOrgVariablesList 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 GetOrgVariablesList Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetOrgVariablesList contentType res accept
-> Limit -> GiteaRequest GetOrgVariablesList contentType res accept
applyOptionalParam GiteaRequest GetOrgVariablesList contentType res accept
req (Limit Int
xs) =
GiteaRequest GetOrgVariablesList contentType res accept
req GiteaRequest GetOrgVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetOrgVariablesList 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 GetOrgVariablesList MimeJSON
orgAddTeamMember
:: Id
-> Username
-> GiteaRequest OrgAddTeamMember MimeNoContent NoContent MimeNoContent
orgAddTeamMember :: Id
-> Username
-> GiteaRequest
OrgAddTeamMember MimeNoContent NoContent MimeNoContent
orgAddTeamMember (Id Integer
id) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgAddTeamMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgAddTeamMember MimeNoContent 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 OrgAddTeamMember
instance Produces OrgAddTeamMember MimeNoContent
orgAddTeamRepository
:: Id
-> Org
-> Repo
-> GiteaRequest OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
orgAddTeamRepository :: Id
-> Org
-> Repo
-> GiteaRequest
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
orgAddTeamRepository (Id Integer
id) (Org Text
org) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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
OrgAddTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgAddTeamRepository MimeNoContent 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 OrgAddTeamRepository
instance Produces OrgAddTeamRepository MimeNoContent
orgConcealMember
:: Org
-> Username
-> GiteaRequest OrgConcealMember MimeNoContent NoContent MimeNoContent
orgConcealMember :: Org
-> Username
-> GiteaRequest
OrgConcealMember MimeNoContent NoContent MimeNoContent
orgConcealMember (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgConcealMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/public_members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgConcealMember MimeNoContent 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 OrgConcealMember
instance Produces OrgConcealMember MimeNoContent
orgCreate
:: (Consumes OrgCreate MimeJSON, MimeRender MimeJSON CreateOrgOption)
=> CreateOrgOption
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
orgCreate :: (Consumes OrgCreate MimeJSON,
MimeRender MimeJSON CreateOrgOption) =>
CreateOrgOption
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
orgCreate CreateOrgOption
organization =
Method
-> [ByteString]
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs"]
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgCreate MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgCreate MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req 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 OrgCreate MimeJSON Organization MimeJSON
-> CreateOrgOption
-> GiteaRequest OrgCreate MimeJSON Organization 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 OrgCreate contentType,
MimeRender contentType CreateOrgOption) =>
GiteaRequest OrgCreate contentType res accept
-> CreateOrgOption -> GiteaRequest OrgCreate contentType res accept
`setBodyParam` CreateOrgOption
organization
data OrgCreate
instance HasBodyParam OrgCreate CreateOrgOption
instance Consumes OrgCreate MimeJSON
instance Produces OrgCreate MimeJSON
orgCreateHook
:: (Consumes OrgCreateHook MimeJSON, MimeRender MimeJSON CreateHookOption)
=> CreateHookOption
-> Org
-> GiteaRequest OrgCreateHook MimeJSON Hook MimeJSON
orgCreateHook :: (Consumes OrgCreateHook MimeJSON,
MimeRender MimeJSON CreateHookOption) =>
CreateHookOption
-> Org -> GiteaRequest OrgCreateHook MimeJSON Hook MimeJSON
orgCreateHook CreateHookOption
body (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgCreateHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/hooks"]
GiteaRequest OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgCreateHook 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 OrgCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgCreateHook 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)
GiteaRequest OrgCreateHook MimeJSON Hook MimeJSON
-> CreateHookOption
-> GiteaRequest OrgCreateHook MimeJSON Hook 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 OrgCreateHook contentType,
MimeRender contentType CreateHookOption) =>
GiteaRequest OrgCreateHook contentType res accept
-> CreateHookOption
-> GiteaRequest OrgCreateHook contentType res accept
`setBodyParam` CreateHookOption
body
data OrgCreateHook
instance HasBodyParam OrgCreateHook CreateHookOption
instance Consumes OrgCreateHook MimeJSON
instance Produces OrgCreateHook MimeJSON
orgCreateLabel
:: (Consumes OrgCreateLabel MimeJSON)
=> Org
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
orgCreateLabel :: Consumes OrgCreateLabel MimeJSON =>
Org -> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
orgCreateLabel (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/labels"]
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgCreateLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgCreateLabel
instance HasBodyParam OrgCreateLabel CreateLabelOption
instance Consumes OrgCreateLabel MimeJSON
instance Produces OrgCreateLabel MimeJSON
orgCreateTeam
:: (Consumes OrgCreateTeam MimeJSON)
=> Org
-> GiteaRequest OrgCreateTeam MimeJSON Team MimeJSON
orgCreateTeam :: Consumes OrgCreateTeam MimeJSON =>
Org -> GiteaRequest OrgCreateTeam MimeJSON Team MimeJSON
orgCreateTeam (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgCreateTeam MimeJSON Team MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/teams"]
GiteaRequest OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgCreateTeam MimeJSON 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 OrgCreateTeam
instance HasBodyParam OrgCreateTeam CreateTeamOption
instance Consumes OrgCreateTeam MimeJSON
instance Produces OrgCreateTeam MimeJSON
orgDelete
:: Org
-> GiteaRequest OrgDelete MimeNoContent NoContent MimeNoContent
orgDelete :: Org -> GiteaRequest OrgDelete MimeNoContent NoContent MimeNoContent
orgDelete (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgDelete MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org]
GiteaRequest OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgDelete MimeNoContent 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 OrgDelete
instance Produces OrgDelete MimeNoContent
orgDeleteAvatar
:: Org
-> GiteaRequest OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
orgDeleteAvatar :: Org
-> GiteaRequest
OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
orgDeleteAvatar (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/avatar"]
GiteaRequest OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgDeleteAvatar MimeNoContent 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 OrgDeleteAvatar
instance Produces OrgDeleteAvatar MimeNoContent
orgDeleteHook
:: Org
-> Id
-> GiteaRequest OrgDeleteHook MimeNoContent NoContent MimeNoContent
orgDeleteHook :: Org
-> Id
-> GiteaRequest OrgDeleteHook MimeNoContent NoContent MimeNoContent
orgDeleteHook (Org Text
org) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgDeleteHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgDeleteHook MimeNoContent 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 OrgDeleteHook
instance Produces OrgDeleteHook MimeNoContent
orgDeleteLabel
:: Org
-> Id
-> GiteaRequest OrgDeleteLabel MimeNoContent NoContent MimeNoContent
orgDeleteLabel :: Org
-> Id
-> GiteaRequest
OrgDeleteLabel MimeNoContent NoContent MimeNoContent
orgDeleteLabel (Org Text
org) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
OrgDeleteLabel MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgDeleteLabel MimeNoContent 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 OrgDeleteLabel
instance Produces OrgDeleteLabel MimeNoContent
orgDeleteMember
:: Org
-> Username
-> GiteaRequest OrgDeleteMember MimeNoContent NoContent MimeNoContent
orgDeleteMember :: Org
-> Username
-> GiteaRequest
OrgDeleteMember MimeNoContent NoContent MimeNoContent
orgDeleteMember (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgDeleteMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgDeleteMember MimeNoContent 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 OrgDeleteMember
instance Produces OrgDeleteMember MimeNoContent
orgDeleteTeam
:: Id
-> GiteaRequest OrgDeleteTeam MimeNoContent NoContent MimeNoContent
orgDeleteTeam :: Id
-> GiteaRequest OrgDeleteTeam MimeNoContent NoContent MimeNoContent
orgDeleteTeam (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgDeleteTeam MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgDeleteTeam MimeNoContent 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 OrgDeleteTeam
instance Produces OrgDeleteTeam MimeNoContent
orgEdit
:: (Consumes OrgEdit MimeJSON, MimeRender MimeJSON EditOrgOption)
=> EditOrgOption
-> Org
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
orgEdit :: (Consumes OrgEdit MimeJSON, MimeRender MimeJSON EditOrgOption) =>
EditOrgOption
-> Org -> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
orgEdit EditOrgOption
body (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org]
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgEdit MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgEdit MimeJSON Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req 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 OrgEdit MimeJSON Organization MimeJSON
-> EditOrgOption
-> GiteaRequest OrgEdit MimeJSON Organization 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 OrgEdit contentType,
MimeRender contentType EditOrgOption) =>
GiteaRequest OrgEdit contentType res accept
-> EditOrgOption -> GiteaRequest OrgEdit contentType res accept
`setBodyParam` EditOrgOption
body
data OrgEdit
instance HasBodyParam OrgEdit EditOrgOption
instance Consumes OrgEdit MimeJSON
instance Produces OrgEdit MimeJSON
orgEditHook
:: (Consumes OrgEditHook MimeJSON)
=> Org
-> Id
-> GiteaRequest OrgEditHook MimeJSON Hook MimeJSON
orgEditHook :: Consumes OrgEditHook MimeJSON =>
Org -> Id -> GiteaRequest OrgEditHook MimeJSON Hook MimeJSON
orgEditHook (Org Text
org) (Id Integer
id) =
Method
-> [ByteString] -> GiteaRequest OrgEditHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgEditHook 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 OrgEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgEditHook 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 OrgEditHook
instance HasBodyParam OrgEditHook EditHookOption
instance Consumes OrgEditHook MimeJSON
instance Produces OrgEditHook MimeJSON
orgEditLabel
:: (Consumes OrgEditLabel MimeJSON)
=> Org
-> Id
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
orgEditLabel :: Consumes OrgEditLabel MimeJSON =>
Org -> Id -> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
orgEditLabel (Org Text
org) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgEditLabel MimeJSON Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgEditLabel
instance HasBodyParam OrgEditLabel EditLabelOption
instance Consumes OrgEditLabel MimeJSON
instance Produces OrgEditLabel MimeJSON
orgEditTeam
:: (Consumes OrgEditTeam MimeJSON)
=> IdInt
-> GiteaRequest OrgEditTeam MimeJSON Team MimeJSON
orgEditTeam :: Consumes OrgEditTeam MimeJSON =>
IdInt -> GiteaRequest OrgEditTeam MimeJSON Team MimeJSON
orgEditTeam (IdInt Int
id) =
Method
-> [ByteString] -> GiteaRequest OrgEditTeam MimeJSON Team MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/teams/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
GiteaRequest OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam MimeJSON Team MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgEditTeam MimeJSON 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 OrgEditTeam
instance HasBodyParam OrgEditTeam EditTeamOption
instance Consumes OrgEditTeam MimeJSON
instance Produces OrgEditTeam MimeJSON
orgGet
:: Org
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
orgGet :: Org -> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
orgGet (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org]
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgGet MimeNoContent Organization MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgGet MimeNoContent Organization MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgGet
instance Produces OrgGet MimeJSON
orgGetAll
:: GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
orgGetAll :: GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
orgGetAll =
Method
-> [ByteString]
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs"]
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgGetAll MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgGetAll
instance HasOptionalParam OrgGetAll Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgGetAll contentType res accept
-> Page -> GiteaRequest OrgGetAll contentType res accept
applyOptionalParam GiteaRequest OrgGetAll contentType res accept
req (Page Int
xs) =
GiteaRequest OrgGetAll contentType res accept
req GiteaRequest OrgGetAll contentType res accept
-> [QueryItem] -> GiteaRequest OrgGetAll 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 OrgGetAll Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgGetAll contentType res accept
-> Limit -> GiteaRequest OrgGetAll contentType res accept
applyOptionalParam GiteaRequest OrgGetAll contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgGetAll contentType res accept
req GiteaRequest OrgGetAll contentType res accept
-> [QueryItem] -> GiteaRequest OrgGetAll 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 OrgGetAll MimeJSON
orgGetHook
:: Org
-> Id
-> GiteaRequest OrgGetHook MimeNoContent Hook MimeJSON
orgGetHook :: Org -> Id -> GiteaRequest OrgGetHook MimeNoContent Hook MimeJSON
orgGetHook (Org Text
org) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgGetHook MimeNoContent Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgGetHook 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 OrgGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgGetHook 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 OrgGetHook
instance Produces OrgGetHook MimeJSON
orgGetLabel
:: Org
-> Id
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
orgGetLabel :: Org -> Id -> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
orgGetLabel (Org Text
org) (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/labels/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgGetLabel MimeNoContent Label MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgGetLabel
instance Produces OrgGetLabel MimeJSON
orgGetRunnerRegistrationToken
:: Org
-> GiteaRequest OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
orgGetRunnerRegistrationToken :: Org
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
orgGetRunnerRegistrationToken (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/runners/registration-token"]
GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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
OrgGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgGetRunnerRegistrationToken MimeNoContent 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 OrgGetRunnerRegistrationToken
instance Produces OrgGetRunnerRegistrationToken MimeNoContent
orgGetTeam
:: Id
-> GiteaRequest OrgGetTeam MimeNoContent Team MimeJSON
orgGetTeam :: Id -> GiteaRequest OrgGetTeam MimeNoContent Team MimeJSON
orgGetTeam (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgGetTeam MimeNoContent Team MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgGetTeam 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 OrgGetTeam MimeNoContent Team MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgGetTeam 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 OrgGetTeam
instance Produces OrgGetTeam MimeJSON
orgGetUserPermissions
:: Username
-> Org
-> GiteaRequest OrgGetUserPermissions MimeNoContent OrganizationPermissions MimeJSON
orgGetUserPermissions :: Username
-> Org
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
orgGetUserPermissions (Username Text
username) (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/permissions"]
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgGetUserPermissions
MimeNoContent
OrganizationPermissions
MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgGetUserPermissions
instance Produces OrgGetUserPermissions MimeJSON
orgIsMember
:: Org
-> Username
-> GiteaRequest OrgIsMember MimeNoContent NoContent MimeNoContent
orgIsMember :: Org
-> Username
-> GiteaRequest OrgIsMember MimeNoContent NoContent MimeNoContent
orgIsMember (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest OrgIsMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgIsMember MimeNoContent 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 OrgIsMember
instance Produces OrgIsMember MimeNoContent
orgIsPublicMember
:: Org
-> Username
-> GiteaRequest OrgIsPublicMember MimeNoContent NoContent MimeNoContent
orgIsPublicMember :: Org
-> Username
-> GiteaRequest
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
orgIsPublicMember (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/public_members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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
OrgIsPublicMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgIsPublicMember MimeNoContent 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 OrgIsPublicMember
instance Produces OrgIsPublicMember MimeNoContent
orgListActionsSecrets
:: Org
-> GiteaRequest OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
orgListActionsSecrets :: Org
-> GiteaRequest
OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
orgListActionsSecrets (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/secrets"]
GiteaRequest OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets MimeNoContent [Secret] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListActionsSecrets 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 OrgListActionsSecrets
instance HasOptionalParam OrgListActionsSecrets Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListActionsSecrets contentType res accept
-> Page
-> GiteaRequest OrgListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest OrgListActionsSecrets contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListActionsSecrets contentType res accept
req GiteaRequest OrgListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListActionsSecrets 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 OrgListActionsSecrets Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListActionsSecrets contentType res accept
-> Limit
-> GiteaRequest OrgListActionsSecrets contentType res accept
applyOptionalParam GiteaRequest OrgListActionsSecrets contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListActionsSecrets contentType res accept
req GiteaRequest OrgListActionsSecrets contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListActionsSecrets 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 OrgListActionsSecrets MimeJSON
orgListActivityFeeds
:: Org
-> GiteaRequest OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
orgListActivityFeeds :: Org
-> GiteaRequest
OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
orgListActivityFeeds (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/activities/feeds"]
GiteaRequest OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListActivityFeeds 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 OrgListActivityFeeds
instance HasOptionalParam OrgListActivityFeeds ParamDate where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListActivityFeeds contentType res accept
-> ParamDate
-> GiteaRequest OrgListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListActivityFeeds contentType res accept
req (ParamDate Date
xs) =
GiteaRequest OrgListActivityFeeds contentType res accept
req GiteaRequest OrgListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListActivityFeeds 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 OrgListActivityFeeds Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListActivityFeeds contentType res accept
-> Page -> GiteaRequest OrgListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListActivityFeeds contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListActivityFeeds contentType res accept
req GiteaRequest OrgListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListActivityFeeds 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 OrgListActivityFeeds Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListActivityFeeds contentType res accept
-> Limit
-> GiteaRequest OrgListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListActivityFeeds contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListActivityFeeds contentType res accept
req GiteaRequest OrgListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListActivityFeeds 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 OrgListActivityFeeds MimeJSON
orgListCurrentUserOrgs
:: GiteaRequest OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
orgListCurrentUserOrgs :: GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
orgListCurrentUserOrgs =
Method
-> [ByteString]
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/orgs"]
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListCurrentUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgListCurrentUserOrgs
instance HasOptionalParam OrgListCurrentUserOrgs Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListCurrentUserOrgs contentType res accept
-> Page
-> GiteaRequest OrgListCurrentUserOrgs contentType res accept
applyOptionalParam GiteaRequest OrgListCurrentUserOrgs contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListCurrentUserOrgs contentType res accept
req GiteaRequest OrgListCurrentUserOrgs contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListCurrentUserOrgs 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 OrgListCurrentUserOrgs Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListCurrentUserOrgs contentType res accept
-> Limit
-> GiteaRequest OrgListCurrentUserOrgs contentType res accept
applyOptionalParam GiteaRequest OrgListCurrentUserOrgs contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListCurrentUserOrgs contentType res accept
req GiteaRequest OrgListCurrentUserOrgs contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListCurrentUserOrgs 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 OrgListCurrentUserOrgs MimeJSON
orgListHooks
:: Org
-> GiteaRequest OrgListHooks MimeNoContent [Hook] MimeJSON
orgListHooks :: Org -> GiteaRequest OrgListHooks MimeNoContent [Hook] MimeJSON
orgListHooks (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListHooks MimeNoContent [Hook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/hooks"]
GiteaRequest OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListHooks 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 OrgListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListHooks 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 OrgListHooks
instance HasOptionalParam OrgListHooks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListHooks contentType res accept
-> Page -> GiteaRequest OrgListHooks contentType res accept
applyOptionalParam GiteaRequest OrgListHooks contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListHooks contentType res accept
req GiteaRequest OrgListHooks contentType res accept
-> [QueryItem] -> GiteaRequest OrgListHooks 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 OrgListHooks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListHooks contentType res accept
-> Limit -> GiteaRequest OrgListHooks contentType res accept
applyOptionalParam GiteaRequest OrgListHooks contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListHooks contentType res accept
req GiteaRequest OrgListHooks contentType res accept
-> [QueryItem] -> GiteaRequest OrgListHooks 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 OrgListHooks MimeJSON
orgListLabels
:: Org
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
orgListLabels :: Org -> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
orgListLabels (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/labels"]
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListLabels MimeNoContent [Label] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgListLabels
instance HasOptionalParam OrgListLabels Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListLabels contentType res accept
-> Page -> GiteaRequest OrgListLabels contentType res accept
applyOptionalParam GiteaRequest OrgListLabels contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListLabels contentType res accept
req GiteaRequest OrgListLabels contentType res accept
-> [QueryItem] -> GiteaRequest OrgListLabels 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 OrgListLabels Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListLabels contentType res accept
-> Limit -> GiteaRequest OrgListLabels contentType res accept
applyOptionalParam GiteaRequest OrgListLabels contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListLabels contentType res accept
req GiteaRequest OrgListLabels contentType res accept
-> [QueryItem] -> GiteaRequest OrgListLabels 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 OrgListLabels MimeJSON
orgListMembers
:: Org
-> GiteaRequest OrgListMembers MimeNoContent [User] MimeJSON
orgListMembers :: Org -> GiteaRequest OrgListMembers MimeNoContent [User] MimeJSON
orgListMembers (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListMembers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/members"]
GiteaRequest OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListMembers 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 OrgListMembers
instance HasOptionalParam OrgListMembers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListMembers contentType res accept
-> Page -> GiteaRequest OrgListMembers contentType res accept
applyOptionalParam GiteaRequest OrgListMembers contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListMembers contentType res accept
req GiteaRequest OrgListMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListMembers 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 OrgListMembers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListMembers contentType res accept
-> Limit -> GiteaRequest OrgListMembers contentType res accept
applyOptionalParam GiteaRequest OrgListMembers contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListMembers contentType res accept
req GiteaRequest OrgListMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListMembers 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 OrgListMembers MimeJSON
orgListPublicMembers
:: Org
-> GiteaRequest OrgListPublicMembers MimeNoContent [User] MimeJSON
orgListPublicMembers :: Org
-> GiteaRequest OrgListPublicMembers MimeNoContent [User] MimeJSON
orgListPublicMembers (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListPublicMembers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/public_members"]
GiteaRequest OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers
instance HasOptionalParam OrgListPublicMembers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListPublicMembers contentType res accept
-> Page -> GiteaRequest OrgListPublicMembers contentType res accept
applyOptionalParam GiteaRequest OrgListPublicMembers contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListPublicMembers contentType res accept
req GiteaRequest OrgListPublicMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListPublicMembers contentType res accept
-> Limit
-> GiteaRequest OrgListPublicMembers contentType res accept
applyOptionalParam GiteaRequest OrgListPublicMembers contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListPublicMembers contentType res accept
req GiteaRequest OrgListPublicMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListPublicMembers 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 OrgListPublicMembers MimeJSON
orgListRepos
:: Org
-> GiteaRequest OrgListRepos MimeNoContent [Repository] MimeJSON
orgListRepos :: Org
-> GiteaRequest OrgListRepos MimeNoContent [Repository] MimeJSON
orgListRepos (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListRepos MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/repos"]
GiteaRequest OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListRepos 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 OrgListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListRepos 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 OrgListRepos
instance HasOptionalParam OrgListRepos Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListRepos contentType res accept
-> Page -> GiteaRequest OrgListRepos contentType res accept
applyOptionalParam GiteaRequest OrgListRepos contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListRepos contentType res accept
req GiteaRequest OrgListRepos contentType res accept
-> [QueryItem] -> GiteaRequest OrgListRepos 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 OrgListRepos Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListRepos contentType res accept
-> Limit -> GiteaRequest OrgListRepos contentType res accept
applyOptionalParam GiteaRequest OrgListRepos contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListRepos contentType res accept
req GiteaRequest OrgListRepos contentType res accept
-> [QueryItem] -> GiteaRequest OrgListRepos 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 OrgListRepos MimeJSON
orgListTeamActivityFeeds
:: Id
-> GiteaRequest OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
orgListTeamActivityFeeds :: Id
-> GiteaRequest
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
orgListTeamActivityFeeds (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/activities/feeds"]
GiteaRequest
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListTeamActivityFeeds 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
OrgListTeamActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListTeamActivityFeeds 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 OrgListTeamActivityFeeds
instance HasOptionalParam OrgListTeamActivityFeeds ParamDate where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> ParamDate
-> GiteaRequest OrgListTeamActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListTeamActivityFeeds contentType res accept
req (ParamDate Date
xs) =
GiteaRequest OrgListTeamActivityFeeds contentType res accept
req GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamActivityFeeds 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 OrgListTeamActivityFeeds Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> Page
-> GiteaRequest OrgListTeamActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListTeamActivityFeeds contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListTeamActivityFeeds contentType res accept
req GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamActivityFeeds 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 OrgListTeamActivityFeeds Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> Limit
-> GiteaRequest OrgListTeamActivityFeeds contentType res accept
applyOptionalParam GiteaRequest OrgListTeamActivityFeeds contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListTeamActivityFeeds contentType res accept
req GiteaRequest OrgListTeamActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamActivityFeeds 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 OrgListTeamActivityFeeds MimeJSON
orgListTeamMember
:: Id
-> Username
-> GiteaRequest OrgListTeamMember MimeNoContent User MimeJSON
orgListTeamMember :: Id
-> Username
-> GiteaRequest OrgListTeamMember MimeNoContent User MimeJSON
orgListTeamMember (Id Integer
id) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest OrgListTeamMember MimeNoContent User MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember MimeNoContent User MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListTeamMember 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 OrgListTeamMember
instance Produces OrgListTeamMember MimeJSON
orgListTeamMembers
:: Id
-> GiteaRequest OrgListTeamMembers MimeNoContent [User] MimeJSON
orgListTeamMembers :: Id -> GiteaRequest OrgListTeamMembers MimeNoContent [User] MimeJSON
orgListTeamMembers (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest OrgListTeamMembers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/members"]
GiteaRequest OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers
instance HasOptionalParam OrgListTeamMembers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamMembers contentType res accept
-> Page -> GiteaRequest OrgListTeamMembers contentType res accept
applyOptionalParam GiteaRequest OrgListTeamMembers contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListTeamMembers contentType res accept
req GiteaRequest OrgListTeamMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamMembers contentType res accept
-> Limit -> GiteaRequest OrgListTeamMembers contentType res accept
applyOptionalParam GiteaRequest OrgListTeamMembers contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListTeamMembers contentType res accept
req GiteaRequest OrgListTeamMembers contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamMembers 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 OrgListTeamMembers MimeJSON
orgListTeamRepo
:: Id
-> Org
-> Repo
-> GiteaRequest OrgListTeamRepo MimeNoContent Repository MimeJSON
orgListTeamRepo :: Id
-> Org
-> Repo
-> GiteaRequest OrgListTeamRepo MimeNoContent Repository MimeJSON
orgListTeamRepo (Id Integer
id) (Org Text
org) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest OrgListTeamRepo MimeNoContent Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo MimeNoContent Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListTeamRepo 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 OrgListTeamRepo
instance Produces OrgListTeamRepo MimeJSON
orgListTeamRepos
:: Id
-> GiteaRequest OrgListTeamRepos MimeNoContent [Repository] MimeJSON
orgListTeamRepos :: Id
-> GiteaRequest
OrgListTeamRepos MimeNoContent [Repository] MimeJSON
orgListTeamRepos (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
OrgListTeamRepos MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/repos"]
GiteaRequest OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListTeamRepos 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 OrgListTeamRepos
instance HasOptionalParam OrgListTeamRepos Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamRepos contentType res accept
-> Page -> GiteaRequest OrgListTeamRepos contentType res accept
applyOptionalParam GiteaRequest OrgListTeamRepos contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListTeamRepos contentType res accept
req GiteaRequest OrgListTeamRepos contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamRepos 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 OrgListTeamRepos Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeamRepos contentType res accept
-> Limit -> GiteaRequest OrgListTeamRepos contentType res accept
applyOptionalParam GiteaRequest OrgListTeamRepos contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListTeamRepos contentType res accept
req GiteaRequest OrgListTeamRepos contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListTeamRepos 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 OrgListTeamRepos MimeJSON
orgListTeams
:: Org
-> GiteaRequest OrgListTeams MimeNoContent [Team] MimeJSON
orgListTeams :: Org -> GiteaRequest OrgListTeams MimeNoContent [Team] MimeJSON
orgListTeams (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgListTeams MimeNoContent [Team] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/teams"]
GiteaRequest OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgListTeams 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 OrgListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgListTeams 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 OrgListTeams
instance HasOptionalParam OrgListTeams Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeams contentType res accept
-> Page -> GiteaRequest OrgListTeams contentType res accept
applyOptionalParam GiteaRequest OrgListTeams contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListTeams contentType res accept
req GiteaRequest OrgListTeams contentType res accept
-> [QueryItem] -> GiteaRequest OrgListTeams 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 OrgListTeams Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListTeams contentType res accept
-> Limit -> GiteaRequest OrgListTeams contentType res accept
applyOptionalParam GiteaRequest OrgListTeams contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListTeams contentType res accept
req GiteaRequest OrgListTeams contentType res accept
-> [QueryItem] -> GiteaRequest OrgListTeams 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 OrgListTeams MimeJSON
orgListUserOrgs
:: Username
-> GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
orgListUserOrgs :: Username
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
orgListUserOrgs (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/orgs"]
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest OrgListUserOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgListUserOrgs MimeNoContent [Organization] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data OrgListUserOrgs
instance HasOptionalParam OrgListUserOrgs Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListUserOrgs contentType res accept
-> Page -> GiteaRequest OrgListUserOrgs contentType res accept
applyOptionalParam GiteaRequest OrgListUserOrgs contentType res accept
req (Page Int
xs) =
GiteaRequest OrgListUserOrgs contentType res accept
req GiteaRequest OrgListUserOrgs contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListUserOrgs 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 OrgListUserOrgs Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrgListUserOrgs contentType res accept
-> Limit -> GiteaRequest OrgListUserOrgs contentType res accept
applyOptionalParam GiteaRequest OrgListUserOrgs contentType res accept
req (Limit Int
xs) =
GiteaRequest OrgListUserOrgs contentType res accept
req GiteaRequest OrgListUserOrgs contentType res accept
-> [QueryItem]
-> GiteaRequest OrgListUserOrgs 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 OrgListUserOrgs MimeJSON
orgPublicizeMember
:: Org
-> Username
-> GiteaRequest OrgPublicizeMember MimeNoContent NoContent MimeNoContent
orgPublicizeMember :: Org
-> Username
-> GiteaRequest
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
orgPublicizeMember (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/public_members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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
OrgPublicizeMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgPublicizeMember MimeNoContent 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 OrgPublicizeMember
instance Produces OrgPublicizeMember MimeNoContent
orgRemoveTeamMember
:: Id
-> Username
-> GiteaRequest OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
orgRemoveTeamMember :: Id
-> Username
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
orgRemoveTeamMember (Id Integer
id) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/members/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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
OrgRemoveTeamMember MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgRemoveTeamMember MimeNoContent 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 OrgRemoveTeamMember
instance Produces OrgRemoveTeamMember MimeNoContent
orgRemoveTeamRepository
:: Id
-> Org
-> Repo
-> GiteaRequest OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
orgRemoveTeamRepository :: Id
-> Org
-> Repo
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
orgRemoveTeamRepository (Id Integer
id) (Org Text
org) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/teams/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id,ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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
OrgRemoveTeamRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrgRemoveTeamRepository MimeNoContent 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 OrgRemoveTeamRepository
instance Produces OrgRemoveTeamRepository MimeNoContent
orgUpdateAvatar
:: (Consumes OrgUpdateAvatar contentType)
=> ContentType contentType
-> Org
-> GiteaRequest OrgUpdateAvatar contentType NoContent MimeNoContent
orgUpdateAvatar :: forall contentType.
Consumes OrgUpdateAvatar contentType =>
ContentType contentType
-> Org
-> GiteaRequest OrgUpdateAvatar contentType NoContent MimeNoContent
orgUpdateAvatar ContentType contentType
_ (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest OrgUpdateAvatar contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/avatar"]
GiteaRequest OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest OrgUpdateAvatar 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 OrgUpdateAvatar
instance HasBodyParam OrgUpdateAvatar UpdateUserAvatarOption
instance Consumes OrgUpdateAvatar MimeJSON
instance Consumes OrgUpdateAvatar MimePlainText
instance Produces OrgUpdateAvatar MimeNoContent
organizationBlockUser
:: Org
-> Username
-> GiteaRequest OrganizationBlockUser MimeNoContent NoContent MimeNoContent
organizationBlockUser :: Org
-> Username
-> GiteaRequest
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
organizationBlockUser (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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
OrganizationBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrganizationBlockUser MimeNoContent 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 OrganizationBlockUser
instance HasOptionalParam OrganizationBlockUser Note2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrganizationBlockUser contentType res accept
-> Note2
-> GiteaRequest OrganizationBlockUser contentType res accept
applyOptionalParam GiteaRequest OrganizationBlockUser contentType res accept
req (Note2 Text
xs) =
GiteaRequest OrganizationBlockUser contentType res accept
req GiteaRequest OrganizationBlockUser contentType res accept
-> [QueryItem]
-> GiteaRequest OrganizationBlockUser 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
"note", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces OrganizationBlockUser MimeNoContent
organizationCheckUserBlock
:: Org
-> Username
-> GiteaRequest OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
organizationCheckUserBlock :: Org
-> Username
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
organizationCheckUserBlock (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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
OrganizationCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrganizationCheckUserBlock MimeNoContent 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 OrganizationCheckUserBlock
instance Produces OrganizationCheckUserBlock MimeNoContent
organizationListBlocks
:: Org
-> GiteaRequest OrganizationListBlocks MimeNoContent [User] MimeJSON
organizationListBlocks :: Org
-> GiteaRequest
OrganizationListBlocks MimeNoContent [User] MimeJSON
organizationListBlocks (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
OrganizationListBlocks MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/blocks"]
GiteaRequest OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrganizationListBlocks 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 OrganizationListBlocks
instance HasOptionalParam OrganizationListBlocks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrganizationListBlocks contentType res accept
-> Page
-> GiteaRequest OrganizationListBlocks contentType res accept
applyOptionalParam GiteaRequest OrganizationListBlocks contentType res accept
req (Page Int
xs) =
GiteaRequest OrganizationListBlocks contentType res accept
req GiteaRequest OrganizationListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest OrganizationListBlocks 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 OrganizationListBlocks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest OrganizationListBlocks contentType res accept
-> Limit
-> GiteaRequest OrganizationListBlocks contentType res accept
applyOptionalParam GiteaRequest OrganizationListBlocks contentType res accept
req (Limit Int
xs) =
GiteaRequest OrganizationListBlocks contentType res accept
req GiteaRequest OrganizationListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest OrganizationListBlocks 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 OrganizationListBlocks MimeJSON
organizationUnblockUser
:: Org
-> Username
-> GiteaRequest OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
organizationUnblockUser :: Org
-> Username
-> GiteaRequest
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
organizationUnblockUser (Org Text
org) (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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
OrganizationUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
OrganizationUnblockUser MimeNoContent 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 OrganizationUnblockUser
instance Produces OrganizationUnblockUser MimeNoContent
teamSearch
:: Org
-> GiteaRequest TeamSearch MimeNoContent TeamSearch200Response MimeJSON
teamSearch :: Org
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
teamSearch (Org Text
org) =
Method
-> [ByteString]
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/teams/search"]
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
TeamSearch MimeNoContent TeamSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data TeamSearch
instance HasOptionalParam TeamSearch Q where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TeamSearch contentType res accept
-> Q -> GiteaRequest TeamSearch contentType res accept
applyOptionalParam GiteaRequest TeamSearch contentType res accept
req (Q Text
xs) =
GiteaRequest TeamSearch contentType res accept
req GiteaRequest TeamSearch contentType res accept
-> [QueryItem] -> GiteaRequest TeamSearch 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 TeamSearch IncludeDesc where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TeamSearch contentType res accept
-> IncludeDesc -> GiteaRequest TeamSearch contentType res accept
applyOptionalParam GiteaRequest TeamSearch contentType res accept
req (IncludeDesc Bool
xs) =
GiteaRequest TeamSearch contentType res accept
req GiteaRequest TeamSearch contentType res accept
-> [QueryItem] -> GiteaRequest TeamSearch 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
"include_desc", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam TeamSearch Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TeamSearch contentType res accept
-> Page -> GiteaRequest TeamSearch contentType res accept
applyOptionalParam GiteaRequest TeamSearch contentType res accept
req (Page Int
xs) =
GiteaRequest TeamSearch contentType res accept
req GiteaRequest TeamSearch contentType res accept
-> [QueryItem] -> GiteaRequest TeamSearch 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 TeamSearch Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest TeamSearch contentType res accept
-> Limit -> GiteaRequest TeamSearch contentType res accept
applyOptionalParam GiteaRequest TeamSearch contentType res accept
req (Limit Int
xs) =
GiteaRequest TeamSearch contentType res accept
req GiteaRequest TeamSearch contentType res accept
-> [QueryItem] -> GiteaRequest TeamSearch 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 TeamSearch MimeJSON
updateOrgSecret
:: (Consumes UpdateOrgSecret MimeJSON)
=> Org
-> Secretname
-> GiteaRequest UpdateOrgSecret MimeJSON NoContent MimeNoContent
updateOrgSecret :: Consumes UpdateOrgSecret MimeJSON =>
Org
-> Secretname
-> GiteaRequest UpdateOrgSecret MimeJSON NoContent MimeNoContent
updateOrgSecret (Org Text
org) (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest UpdateOrgSecret MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateOrgSecret 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 UpdateOrgSecret
instance HasBodyParam UpdateOrgSecret CreateOrUpdateSecretOption
instance Consumes UpdateOrgSecret MimeJSON
instance Produces UpdateOrgSecret MimeNoContent
updateOrgVariable
:: (Consumes UpdateOrgVariable MimeJSON)
=> Org
-> Variablename
-> GiteaRequest UpdateOrgVariable MimeJSON NoContent MimeNoContent
updateOrgVariable :: Consumes UpdateOrgVariable MimeJSON =>
Org
-> Variablename
-> GiteaRequest UpdateOrgVariable MimeJSON NoContent MimeNoContent
updateOrgVariable (Org Text
org) (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest UpdateOrgVariable MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/orgs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
org,ByteString
"/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateOrgVariable 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 UpdateOrgVariable
instance HasBodyParam UpdateOrgVariable UpdateVariableOption
instance Consumes UpdateOrgVariable MimeJSON
instance Produces UpdateOrgVariable MimeNoContent