{-
   Gitea API

   This documentation describes the Gitea API.

   OpenAPI Version: 3.0.1
   Gitea API API version: 1.23.1
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Gitea.API.Admin
-}

{-# 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.Admin where

import Gitea.Core
import Gitea.MimeTypes
import Gitea.Model as M

import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Set as Set
import qualified Data.String as P
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Time as TI
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Media as ME
import qualified Network.HTTP.Types as NH
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH

import Data.Text (Text)
import GHC.Base ((<|>))

import Prelude ((==),(/=),($), (.),(<$>),(<*>),(>>=),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P

-- * Operations


-- ** Admin

-- *** adminAddUserBadges

-- | @POST \/admin\/users\/{username}\/badges@
-- 
-- Add a badge to a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminAddUserBadges
  :: (Consumes AdminAddUserBadges MimeJSON)
  => Username -- ^ "username" -  username of user
  -> GiteaRequest AdminAddUserBadges MimeJSON NoContent MimeNoContent
adminAddUserBadges :: Consumes AdminAddUserBadges MimeJSON =>
Username
-> GiteaRequest AdminAddUserBadges MimeJSON NoContent MimeNoContent
adminAddUserBadges (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminAddUserBadges MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/badges"]
    GiteaRequest AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminAddUserBadges 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 AdminAddUserBadges 
instance HasBodyParam AdminAddUserBadges UserBadgeOption 

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

instance Produces AdminAddUserBadges MimeNoContent


-- *** adminAdoptRepository

-- | @POST \/admin\/unadopted\/{owner}\/{repo}@
-- 
-- Adopt unadopted files as a repository
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminAdoptRepository
  :: Owner -- ^ "owner" -  owner of the repo
  -> Repo -- ^ "repo" -  name of the repo
  -> GiteaRequest AdminAdoptRepository MimeNoContent NoContent MimeNoContent
adminAdoptRepository :: Owner
-> Repo
-> GiteaRequest
     AdminAdoptRepository MimeNoContent NoContent MimeNoContent
adminAdoptRepository (Owner Text
owner) (Repo Text
repo) =
  Method
-> [ByteString]
-> GiteaRequest
     AdminAdoptRepository MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/unadopted/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
    GiteaRequest
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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
  AdminAdoptRepository MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminAdoptRepository MimeNoContent 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 AdminAdoptRepository  
instance Produces AdminAdoptRepository MimeNoContent


-- *** adminCreateHook

-- | @POST \/admin\/hooks@
-- 
-- Create a hook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCreateHook
  :: (Consumes AdminCreateHook MimeJSON, MimeRender MimeJSON CreateHookOption)
  => CreateHookOption -- ^ "body"
  -> GiteaRequest AdminCreateHook MimeJSON Hook MimeJSON
adminCreateHook :: (Consumes AdminCreateHook MimeJSON,
 MimeRender MimeJSON CreateHookOption) =>
CreateHookOption
-> GiteaRequest AdminCreateHook MimeJSON Hook MimeJSON
adminCreateHook CreateHookOption
body =
  Method
-> [ByteString]
-> GiteaRequest AdminCreateHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/hooks"]
    GiteaRequest AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCreateHook 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 AdminCreateHook MimeJSON Hook MimeJSON
-> CreateHookOption
-> GiteaRequest AdminCreateHook 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 AdminCreateHook contentType,
 MimeRender contentType CreateHookOption) =>
GiteaRequest AdminCreateHook contentType res accept
-> CreateHookOption
-> GiteaRequest AdminCreateHook contentType res accept
`setBodyParam` CreateHookOption
body

data AdminCreateHook 
instance HasBodyParam AdminCreateHook CreateHookOption 

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

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


-- *** adminCreateOrg

-- | @POST \/admin\/users\/{username}\/orgs@
-- 
-- Create an organization
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCreateOrg
  :: (Consumes AdminCreateOrg MimeJSON, MimeRender MimeJSON CreateOrgOption)
  => CreateOrgOption -- ^ "organization"
  -> Username -- ^ "username" -  username of the user that will own the created organization
  -> GiteaRequest AdminCreateOrg MimeJSON Organization MimeJSON
adminCreateOrg :: (Consumes AdminCreateOrg MimeJSON,
 MimeRender MimeJSON CreateOrgOption) =>
CreateOrgOption
-> Username
-> GiteaRequest AdminCreateOrg MimeJSON Organization MimeJSON
adminCreateOrg CreateOrgOption
organization (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminCreateOrg MimeJSON Organization MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/orgs"]
    GiteaRequest AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg MimeJSON Organization MimeJSON
-> CreateOrgOption
-> GiteaRequest AdminCreateOrg 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 AdminCreateOrg contentType,
 MimeRender contentType CreateOrgOption) =>
GiteaRequest AdminCreateOrg contentType res accept
-> CreateOrgOption
-> GiteaRequest AdminCreateOrg contentType res accept
`setBodyParam` CreateOrgOption
organization

data AdminCreateOrg 
instance HasBodyParam AdminCreateOrg CreateOrgOption 

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

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


-- *** adminCreatePublicKey

-- | @POST \/admin\/users\/{username}\/keys@
-- 
-- Add a public key on behalf of a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCreatePublicKey
  :: (Consumes AdminCreatePublicKey MimeJSON)
  => Username -- ^ "username" -  username of the user
  -> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
adminCreatePublicKey :: Consumes AdminCreatePublicKey MimeJSON =>
Username
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
adminCreatePublicKey (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/keys"]
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCreatePublicKey MimeJSON PublicKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data AdminCreatePublicKey 
instance HasBodyParam AdminCreatePublicKey CreateKeyOption 

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

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


-- *** adminCreateRepo

-- | @POST \/admin\/users\/{username}\/repos@
-- 
-- Create a repository on behalf of a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCreateRepo
  :: (Consumes AdminCreateRepo MimeJSON, MimeRender MimeJSON CreateRepoOption)
  => CreateRepoOption -- ^ "repository"
  -> Username -- ^ "username" -  username of the user. This user will own the created repository
  -> GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
adminCreateRepo :: (Consumes AdminCreateRepo MimeJSON,
 MimeRender MimeJSON CreateRepoOption) =>
CreateRepoOption
-> Username
-> GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
adminCreateRepo CreateRepoOption
repository (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/repos"]
    GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCreateRepo 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 AdminCreateRepo MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCreateRepo 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)
    GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
-> CreateRepoOption
-> GiteaRequest AdminCreateRepo MimeJSON Repository MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes AdminCreateRepo contentType,
 MimeRender contentType CreateRepoOption) =>
GiteaRequest AdminCreateRepo contentType res accept
-> CreateRepoOption
-> GiteaRequest AdminCreateRepo contentType res accept
`setBodyParam` CreateRepoOption
repository

data AdminCreateRepo 
instance HasBodyParam AdminCreateRepo CreateRepoOption 

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

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


-- *** adminCreateUser

-- | @POST \/admin\/users@
-- 
-- Create a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCreateUser
  :: (Consumes AdminCreateUser MimeJSON)
  => GiteaRequest AdminCreateUser MimeJSON User MimeJSON
adminCreateUser :: Consumes AdminCreateUser MimeJSON =>
GiteaRequest AdminCreateUser MimeJSON User MimeJSON
adminCreateUser =
  Method
-> [ByteString]
-> GiteaRequest AdminCreateUser MimeJSON User MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users"]
    GiteaRequest AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCreateUser MimeJSON 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 AdminCreateUser 
instance HasBodyParam AdminCreateUser CreateUserOption 

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

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


-- *** adminCronList

-- | @GET \/admin\/cron@
-- 
-- List cron tasks
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCronList
  :: GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
adminCronList :: GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
adminCronList =
  Method
-> [ByteString]
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/cron"]
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCronList MimeNoContent [Cron] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data AdminCronList  

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

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


-- *** adminCronRun

-- | @POST \/admin\/cron\/{task}@
-- 
-- Run cron task
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminCronRun
  :: Task -- ^ "task" -  task to run
  -> GiteaRequest AdminCronRun MimeNoContent NoContent MimeNoContent
adminCronRun :: Task
-> GiteaRequest AdminCronRun MimeNoContent NoContent MimeNoContent
adminCronRun (Task Text
task) =
  Method
-> [ByteString]
-> GiteaRequest AdminCronRun MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/cron/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
task]
    GiteaRequest AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminCronRun MimeNoContent 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 AdminCronRun  
instance Produces AdminCronRun MimeNoContent


-- *** adminDeleteHook

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


-- *** adminDeleteUnadoptedRepository

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


-- *** adminDeleteUser

-- | @DELETE \/admin\/users\/{username}@
-- 
-- Delete a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminDeleteUser
  :: Username -- ^ "username" -  username of user to delete
  -> GiteaRequest AdminDeleteUser MimeNoContent NoContent MimeNoContent
adminDeleteUser :: Username
-> GiteaRequest
     AdminDeleteUser MimeNoContent NoContent MimeNoContent
adminDeleteUser (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest
     AdminDeleteUser MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
    GiteaRequest AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminDeleteUser MimeNoContent 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 AdminDeleteUser  

-- | /Optional Param/ "purge" - purge the user from the system completely
instance HasOptionalParam AdminDeleteUser Purge where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest AdminDeleteUser contentType res accept
-> Purge -> GiteaRequest AdminDeleteUser contentType res accept
applyOptionalParam GiteaRequest AdminDeleteUser contentType res accept
req (Purge Bool
xs) =
    GiteaRequest AdminDeleteUser contentType res accept
req GiteaRequest AdminDeleteUser contentType res accept
-> [QueryItem]
-> GiteaRequest AdminDeleteUser 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
"purge", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces AdminDeleteUser MimeNoContent


-- *** adminDeleteUserBadges

-- | @DELETE \/admin\/users\/{username}\/badges@
-- 
-- Remove a badge from a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminDeleteUserBadges
  :: (Consumes AdminDeleteUserBadges contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Username -- ^ "username" -  username of user
  -> GiteaRequest AdminDeleteUserBadges contentType NoContent MimeNoContent
adminDeleteUserBadges :: forall contentType.
Consumes AdminDeleteUserBadges contentType =>
ContentType contentType
-> Username
-> GiteaRequest
     AdminDeleteUserBadges contentType NoContent MimeNoContent
adminDeleteUserBadges ContentType contentType
_ (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest
     AdminDeleteUserBadges contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/badges"]
    GiteaRequest
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminDeleteUserBadges 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
  AdminDeleteUserBadges contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminDeleteUserBadges 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 AdminDeleteUserBadges 
instance HasBodyParam AdminDeleteUserBadges UserBadgeOption 

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

instance Produces AdminDeleteUserBadges MimeNoContent


-- *** adminDeleteUserPublicKey

-- | @DELETE \/admin\/users\/{username}\/keys\/{id}@
-- 
-- Delete a user's public key
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminDeleteUserPublicKey
  :: Username -- ^ "username" -  username of user
  -> Id -- ^ "id" -  id of the key to delete
  -> GiteaRequest AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
adminDeleteUserPublicKey :: Username
-> Id
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
adminDeleteUserPublicKey (Username Text
username) (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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
  AdminDeleteUserPublicKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminDeleteUserPublicKey MimeNoContent 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 AdminDeleteUserPublicKey  
instance Produces AdminDeleteUserPublicKey MimeNoContent


-- *** adminEditHook

-- | @PATCH \/admin\/hooks\/{id}@
-- 
-- Update a hook
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminEditHook
  :: (Consumes AdminEditHook MimeJSON)
  => Id -- ^ "id" -  id of the hook to update
  -> GiteaRequest AdminEditHook MimeJSON Hook MimeJSON
adminEditHook :: Consumes AdminEditHook MimeJSON =>
Id -> GiteaRequest AdminEditHook MimeJSON Hook MimeJSON
adminEditHook (Id Integer
id) =
  Method
-> [ByteString]
-> GiteaRequest AdminEditHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/admin/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
    GiteaRequest AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminEditHook 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 AdminEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminEditHook 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 AdminEditHook 
instance HasBodyParam AdminEditHook EditHookOption 

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

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


-- *** adminEditUser

-- | @PATCH \/admin\/users\/{username}@
-- 
-- Edit an existing user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminEditUser
  :: (Consumes AdminEditUser MimeJSON)
  => Username -- ^ "username" -  username of user to edit
  -> GiteaRequest AdminEditUser MimeJSON User MimeJSON
adminEditUser :: Consumes AdminEditUser MimeJSON =>
Username -> GiteaRequest AdminEditUser MimeJSON User MimeJSON
adminEditUser (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminEditUser MimeJSON User MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
    GiteaRequest AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser MimeJSON User MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminEditUser MimeJSON 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 AdminEditUser 
instance HasBodyParam AdminEditUser EditUserOption 

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

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


-- *** adminGetAllEmails

-- | @GET \/admin\/emails@
-- 
-- List all emails
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminGetAllEmails
  :: GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
adminGetAllEmails :: GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
adminGetAllEmails =
  Method
-> [ByteString]
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/emails"]
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminGetAllEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data AdminGetAllEmails  

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

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


-- *** adminGetAllOrgs

-- | @GET \/admin\/orgs@
-- 
-- List all organizations
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminGetAllOrgs
  :: GiteaRequest AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
adminGetAllOrgs :: GiteaRequest AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
adminGetAllOrgs =
  Method
-> [ByteString]
-> GiteaRequest
     AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/orgs"]
    GiteaRequest AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs MimeNoContent [Organization] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminGetAllOrgs 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 AdminGetAllOrgs  

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

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


-- *** adminGetHook

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


-- *** adminGetRunnerRegistrationToken

-- | @GET \/admin\/runners\/registration-token@
-- 
-- Get an global actions runner registration token
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminGetRunnerRegistrationToken
  :: GiteaRequest AdminGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
adminGetRunnerRegistrationToken :: GiteaRequest
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
adminGetRunnerRegistrationToken =
  Method
-> [ByteString]
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     NoContent
     MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/runners/registration-token"]
    GiteaRequest
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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
  AdminGetRunnerRegistrationToken
  MimeNoContent
  NoContent
  MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
     AdminGetRunnerRegistrationToken
     MimeNoContent
     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 AdminGetRunnerRegistrationToken  
instance Produces AdminGetRunnerRegistrationToken MimeNoContent


-- *** adminListHooks

-- | @GET \/admin\/hooks@
-- 
-- List system's webhooks
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminListHooks
  :: GiteaRequest AdminListHooks MimeNoContent [Hook] MimeJSON
adminListHooks :: GiteaRequest AdminListHooks MimeNoContent [Hook] MimeJSON
adminListHooks =
  Method
-> [ByteString]
-> GiteaRequest AdminListHooks MimeNoContent [Hook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/hooks"]
    GiteaRequest AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminListHooks 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 AdminListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminListHooks 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 AdminListHooks  

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

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


-- *** adminListUserBadges

-- | @GET \/admin\/users\/{username}\/badges@
-- 
-- List a user's badges
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminListUserBadges
  :: Username -- ^ "username" -  username of user
  -> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
adminListUserBadges :: Username
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
adminListUserBadges (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/badges"]
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminListUserBadges MimeNoContent [Badge] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

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


-- *** adminRenameUser

-- | @POST \/admin\/users\/{username}\/rename@
-- 
-- Rename a user
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminRenameUser
  :: (Consumes AdminRenameUser contentType, MimeRender contentType RenameUserOption)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> RenameUserOption -- ^ "body"
  -> Username -- ^ "username" -  existing username of user
  -> GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
adminRenameUser :: forall contentType.
(Consumes AdminRenameUser contentType,
 MimeRender contentType RenameUserOption) =>
ContentType contentType
-> RenameUserOption
-> Username
-> GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
adminRenameUser ContentType contentType
_ RenameUserOption
body (Username Text
username) =
  Method
-> [ByteString]
-> GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/rename"]
    GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminRenameUser 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 AdminRenameUser contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
    GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
-> RenameUserOption
-> GiteaRequest AdminRenameUser contentType NoContent MimeNoContent
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
GiteaRequest req contentType res accept
-> param -> GiteaRequest req contentType res accept
forall contentType res accept.
(Consumes AdminRenameUser contentType,
 MimeRender contentType RenameUserOption) =>
GiteaRequest AdminRenameUser contentType res accept
-> RenameUserOption
-> GiteaRequest AdminRenameUser contentType res accept
`setBodyParam` RenameUserOption
body

data AdminRenameUser 
instance HasBodyParam AdminRenameUser RenameUserOption 

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

instance Produces AdminRenameUser MimeNoContent


-- *** adminSearchEmails

-- | @GET \/admin\/emails\/search@
-- 
-- Search all emails
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminSearchEmails
  :: GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
adminSearchEmails :: GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
adminSearchEmails =
  Method
-> [ByteString]
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/emails/search"]
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminSearchEmails MimeNoContent [Email] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data AdminSearchEmails  

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

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

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


-- *** adminSearchUsers

-- | @GET \/admin\/users@
-- 
-- Search users according filter conditions
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminSearchUsers
  :: GiteaRequest AdminSearchUsers MimeNoContent [User] MimeJSON
adminSearchUsers :: GiteaRequest AdminSearchUsers MimeNoContent [User] MimeJSON
adminSearchUsers =
  Method
-> [ByteString]
-> GiteaRequest AdminSearchUsers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/users"]
    GiteaRequest AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminSearchUsers 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 AdminSearchUsers  

-- | /Optional Param/ "source_id" - ID of the user's login source to search for
instance HasOptionalParam AdminSearchUsers SourceId where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest AdminSearchUsers contentType res accept
-> SourceId -> GiteaRequest AdminSearchUsers contentType res accept
applyOptionalParam GiteaRequest AdminSearchUsers contentType res accept
req (SourceId Integer
xs) =
    GiteaRequest AdminSearchUsers contentType res accept
req GiteaRequest AdminSearchUsers contentType res accept
-> [QueryItem]
-> GiteaRequest AdminSearchUsers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"source_id", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "login_name" - user's login name to search for
instance HasOptionalParam AdminSearchUsers LoginName where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest AdminSearchUsers contentType res accept
-> LoginName
-> GiteaRequest AdminSearchUsers contentType res accept
applyOptionalParam GiteaRequest AdminSearchUsers contentType res accept
req (LoginName Text
xs) =
    GiteaRequest AdminSearchUsers contentType res accept
req GiteaRequest AdminSearchUsers contentType res accept
-> [QueryItem]
-> GiteaRequest AdminSearchUsers 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
"login_name", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

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


-- *** adminUnadoptedList

-- | @GET \/admin\/unadopted@
-- 
-- List unadopted repositories
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
adminUnadoptedList
  :: GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
adminUnadoptedList :: GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
adminUnadoptedList =
  Method
-> [ByteString]
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/unadopted"]
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest AdminUnadoptedList MimeNoContent [Text] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data AdminUnadoptedList  

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

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

-- | /Optional Param/ "pattern" - pattern of repositories to search for
instance HasOptionalParam AdminUnadoptedList Pattern where
  applyOptionalParam :: forall contentType res accept.
GiteaRequest AdminUnadoptedList contentType res accept
-> Pattern
-> GiteaRequest AdminUnadoptedList contentType res accept
applyOptionalParam GiteaRequest AdminUnadoptedList contentType res accept
req (Pattern Text
xs) =
    GiteaRequest AdminUnadoptedList contentType res accept
req GiteaRequest AdminUnadoptedList contentType res accept
-> [QueryItem]
-> GiteaRequest AdminUnadoptedList 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
"pattern", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces AdminUnadoptedList MimeJSON