{-# 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.User 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
createCurrentUserRepo0
:: (Consumes CreateCurrentUserRepo0 MimeJSON)
=> GiteaRequest CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
createCurrentUserRepo0 :: Consumes CreateCurrentUserRepo0 MimeJSON =>
GiteaRequest CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
createCurrentUserRepo0 =
Method
-> [ByteString]
-> GiteaRequest CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/repos"]
GiteaRequest CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateCurrentUserRepo0 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 CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateCurrentUserRepo0 MimeJSON Repository MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data CreateCurrentUserRepo0
instance HasBodyParam CreateCurrentUserRepo0 CreateRepoOption
instance Consumes CreateCurrentUserRepo0 MimeJSON
instance Produces CreateCurrentUserRepo0 MimeJSON
createUserVariable
:: (Consumes CreateUserVariable MimeJSON)
=> Variablename
-> GiteaRequest CreateUserVariable MimeJSON NoContent MimeNoContent
createUserVariable :: Consumes CreateUserVariable MimeJSON =>
Variablename
-> GiteaRequest CreateUserVariable MimeJSON NoContent MimeNoContent
createUserVariable (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest CreateUserVariable MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest CreateUserVariable 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 CreateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest CreateUserVariable 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 CreateUserVariable
instance HasBodyParam CreateUserVariable CreateVariableOption
instance Consumes CreateUserVariable MimeJSON
instance Produces CreateUserVariable MimeNoContent
deleteUserSecret
:: Secretname
-> GiteaRequest DeleteUserSecret MimeNoContent NoContent MimeNoContent
deleteUserSecret :: Secretname
-> GiteaRequest
DeleteUserSecret MimeNoContent NoContent MimeNoContent
deleteUserSecret (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest
DeleteUserSecret MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteUserSecret MimeNoContent 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 DeleteUserSecret
instance Produces DeleteUserSecret MimeNoContent
deleteUserVariable
:: Variablename
-> GiteaRequest DeleteUserVariable MimeNoContent NoContent MimeNoContent
deleteUserVariable :: Variablename
-> GiteaRequest
DeleteUserVariable MimeNoContent NoContent MimeNoContent
deleteUserVariable (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
DeleteUserVariable MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
DeleteUserVariable MimeNoContent 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
DeleteUserVariable MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
DeleteUserVariable MimeNoContent 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 DeleteUserVariable
instance Produces DeleteUserVariable MimeNoContent
getUserSettings
:: GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
getUserSettings :: GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
getUserSettings =
Method
-> [ByteString]
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/settings"]
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetUserSettings MimeNoContent [UserSettings] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetUserSettings MimeNoContent [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetUserSettings
instance Produces GetUserSettings MimeJSON
getUserVariable
:: Variablename
-> GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
getUserVariable :: Variablename
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
getUserVariable (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetUserVariable MimeNoContent ActionVariable MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetUserVariable MimeNoContent ActionVariable MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetUserVariable
instance Produces GetUserVariable MimeJSON
getUserVariablesList
:: GiteaRequest GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
getUserVariablesList :: GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
getUserVariablesList =
Method
-> [ByteString]
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/actions/variables"]
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetUserVariablesList MimeNoContent [ActionVariable] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetUserVariablesList
instance HasOptionalParam GetUserVariablesList Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetUserVariablesList contentType res accept
-> Page -> GiteaRequest GetUserVariablesList contentType res accept
applyOptionalParam GiteaRequest GetUserVariablesList contentType res accept
req (Page Int
xs) =
GiteaRequest GetUserVariablesList contentType res accept
req GiteaRequest GetUserVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetUserVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam GetUserVariablesList Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest GetUserVariablesList contentType res accept
-> Limit
-> GiteaRequest GetUserVariablesList contentType res accept
applyOptionalParam GiteaRequest GetUserVariablesList contentType res accept
req (Limit Int
xs) =
GiteaRequest GetUserVariablesList contentType res accept
req GiteaRequest GetUserVariablesList contentType res accept
-> [QueryItem]
-> GiteaRequest GetUserVariablesList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces GetUserVariablesList MimeJSON
getVerificationToken
:: GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
getVerificationToken :: GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
getVerificationToken =
Method
-> [ByteString]
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/gpg_key_token"]
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest GetVerificationToken MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest
GetVerificationToken MimeNoContent Text MimePlainText
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data GetVerificationToken
instance Produces GetVerificationToken MimePlainText
updateUserSecret
:: (Consumes UpdateUserSecret MimeJSON)
=> Secretname
-> GiteaRequest UpdateUserSecret MimeJSON NoContent MimeNoContent
updateUserSecret :: Consumes UpdateUserSecret MimeJSON =>
Secretname
-> GiteaRequest UpdateUserSecret MimeJSON NoContent MimeNoContent
updateUserSecret (Secretname Text
secretname) =
Method
-> [ByteString]
-> GiteaRequest UpdateUserSecret MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/user/actions/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
secretname]
GiteaRequest UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateUserSecret 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 UpdateUserSecret
instance HasBodyParam UpdateUserSecret CreateOrUpdateSecretOption
instance Consumes UpdateUserSecret MimeJSON
instance Produces UpdateUserSecret MimeNoContent
updateUserSettings
:: (Consumes UpdateUserSettings contentType)
=> ContentType contentType
-> GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
updateUserSettings :: forall contentType.
Consumes UpdateUserSettings contentType =>
ContentType contentType
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
updateUserSettings ContentType contentType
_ =
Method
-> [ByteString]
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/user/settings"]
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UpdateUserSettings contentType [UserSettings] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UpdateUserSettings contentType [UserSettings] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UpdateUserSettings
instance HasBodyParam UpdateUserSettings UserSettingsOptions
instance Consumes UpdateUserSettings MimeJSON
instance Consumes UpdateUserSettings MimePlainText
instance Produces UpdateUserSettings MimeJSON
updateUserVariable
:: (Consumes UpdateUserVariable MimeJSON)
=> Variablename
-> GiteaRequest UpdateUserVariable MimeJSON NoContent MimeNoContent
updateUserVariable :: Consumes UpdateUserVariable MimeJSON =>
Variablename
-> GiteaRequest UpdateUserVariable MimeJSON NoContent MimeNoContent
updateUserVariable (Variablename Text
variablename) =
Method
-> [ByteString]
-> GiteaRequest UpdateUserVariable MimeJSON NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/user/actions/variables/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
variablename]
GiteaRequest UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable MimeJSON NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UpdateUserVariable 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 UpdateUserVariable
instance HasBodyParam UpdateUserVariable UpdateVariableOption
instance Consumes UpdateUserVariable MimeJSON
instance Produces UpdateUserVariable MimeNoContent
userAddEmail
:: (Consumes UserAddEmail contentType)
=> ContentType contentType
-> GiteaRequest UserAddEmail contentType [Email] MimeJSON
userAddEmail :: forall contentType.
Consumes UserAddEmail contentType =>
ContentType contentType
-> GiteaRequest UserAddEmail contentType [Email] MimeJSON
userAddEmail ContentType contentType
_ =
Method
-> [ByteString]
-> GiteaRequest UserAddEmail contentType [Email] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/emails"]
GiteaRequest UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail contentType [Email] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserAddEmail contentType [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 UserAddEmail
instance HasBodyParam UserAddEmail CreateEmailOption
instance Consumes UserAddEmail MimeJSON
instance Consumes UserAddEmail MimePlainText
instance Produces UserAddEmail MimeJSON
userBlockUser
:: Username
-> GiteaRequest UserBlockUser MimeNoContent NoContent MimeNoContent
userBlockUser :: Username
-> GiteaRequest UserBlockUser MimeNoContent NoContent MimeNoContent
userBlockUser (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserBlockUser MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/user/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UserBlockUser MimeNoContent 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 UserBlockUser
instance HasOptionalParam UserBlockUser Note2 where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserBlockUser contentType res accept
-> Note2 -> GiteaRequest UserBlockUser contentType res accept
applyOptionalParam GiteaRequest UserBlockUser contentType res accept
req (Note2 Text
xs) =
GiteaRequest UserBlockUser contentType res accept
req GiteaRequest UserBlockUser contentType res accept
-> [QueryItem] -> GiteaRequest UserBlockUser contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"note", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces UserBlockUser MimeNoContent
userCheckFollowing
:: Username
-> Target
-> GiteaRequest UserCheckFollowing MimeNoContent NoContent MimeNoContent
userCheckFollowing :: Username
-> Target
-> GiteaRequest
UserCheckFollowing MimeNoContent NoContent MimeNoContent
userCheckFollowing (Username Text
username) (Target Text
target) =
Method
-> [ByteString]
-> GiteaRequest
UserCheckFollowing MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/following/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
target]
GiteaRequest
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCheckFollowing MimeNoContent 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
UserCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCheckFollowing MimeNoContent 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 UserCheckFollowing
instance Produces UserCheckFollowing MimeNoContent
userCheckUserBlock
:: Username
-> GiteaRequest UserCheckUserBlock MimeNoContent NoContent MimeNoContent
userCheckUserBlock :: Username
-> GiteaRequest
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
userCheckUserBlock (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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
UserCheckUserBlock MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCheckUserBlock MimeNoContent 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 UserCheckUserBlock
instance Produces UserCheckUserBlock MimeNoContent
userCreateHook
:: (Consumes UserCreateHook MimeJSON, MimeRender MimeJSON CreateHookOption)
=> CreateHookOption
-> GiteaRequest UserCreateHook MimeJSON Hook MimeJSON
userCreateHook :: (Consumes UserCreateHook MimeJSON,
MimeRender MimeJSON CreateHookOption) =>
CreateHookOption
-> GiteaRequest UserCreateHook MimeJSON Hook MimeJSON
userCreateHook CreateHookOption
body =
Method
-> [ByteString]
-> GiteaRequest UserCreateHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/hooks"]
GiteaRequest UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCreateHook 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 UserCreateHook MimeJSON Hook MimeJSON
-> CreateHookOption
-> GiteaRequest UserCreateHook 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 UserCreateHook contentType,
MimeRender contentType CreateHookOption) =>
GiteaRequest UserCreateHook contentType res accept
-> CreateHookOption
-> GiteaRequest UserCreateHook contentType res accept
`setBodyParam` CreateHookOption
body
data UserCreateHook
instance HasBodyParam UserCreateHook CreateHookOption
instance Consumes UserCreateHook MimeJSON
instance Produces UserCreateHook MimeJSON
userCreateOAuth2Application
:: (Consumes UserCreateOAuth2Application contentType, MimeRender contentType CreateOAuth2ApplicationOptions)
=> ContentType contentType
-> CreateOAuth2ApplicationOptions
-> GiteaRequest UserCreateOAuth2Application contentType OAuth2Application MimeJSON
userCreateOAuth2Application :: forall contentType.
(Consumes UserCreateOAuth2Application contentType,
MimeRender contentType CreateOAuth2ApplicationOptions) =>
ContentType contentType
-> CreateOAuth2ApplicationOptions
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
userCreateOAuth2Application ContentType contentType
_ CreateOAuth2ApplicationOptions
body =
Method
-> [ByteString]
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/applications/oauth2"]
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req 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
UserCreateOAuth2Application contentType OAuth2Application MimeJSON
-> CreateOAuth2ApplicationOptions
-> GiteaRequest
UserCreateOAuth2Application contentType OAuth2Application 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 UserCreateOAuth2Application contentType,
MimeRender contentType CreateOAuth2ApplicationOptions) =>
GiteaRequest UserCreateOAuth2Application contentType res accept
-> CreateOAuth2ApplicationOptions
-> GiteaRequest UserCreateOAuth2Application contentType res accept
`setBodyParam` CreateOAuth2ApplicationOptions
body
data UserCreateOAuth2Application
instance HasBodyParam UserCreateOAuth2Application CreateOAuth2ApplicationOptions
instance Consumes UserCreateOAuth2Application MimeJSON
instance Consumes UserCreateOAuth2Application MimePlainText
instance Produces UserCreateOAuth2Application MimeJSON
userCreateToken
:: (Consumes UserCreateToken MimeJSON)
=> Username
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
userCreateToken :: Consumes UserCreateToken MimeJSON =>
Username
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
userCreateToken (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/tokens"]
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCreateToken MimeJSON AccessToken MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCreateToken
instance HasBodyParam UserCreateToken CreateAccessTokenOption
instance Consumes UserCreateToken MimeJSON
instance Produces UserCreateToken MimeJSON
userCurrentCheckFollowing
:: Username
-> GiteaRequest UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
userCurrentCheckFollowing :: Username
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
userCurrentCheckFollowing (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/following/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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
UserCurrentCheckFollowing MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentCheckFollowing MimeNoContent 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 UserCurrentCheckFollowing
instance Produces UserCurrentCheckFollowing MimeNoContent
userCurrentCheckStarring
:: Owner
-> Repo
-> GiteaRequest UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
userCurrentCheckStarring :: Owner
-> Repo
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
userCurrentCheckStarring (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/starred/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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
UserCurrentCheckStarring MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentCheckStarring MimeNoContent 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 UserCurrentCheckStarring
instance Produces UserCurrentCheckStarring MimeNoContent
userCurrentDeleteFollow
:: Username
-> GiteaRequest UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
userCurrentDeleteFollow :: Username
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
userCurrentDeleteFollow (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/following/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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
UserCurrentDeleteFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentDeleteFollow MimeNoContent 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 UserCurrentDeleteFollow
instance Produces UserCurrentDeleteFollow MimeNoContent
userCurrentDeleteGPGKey
:: Id
-> GiteaRequest UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
userCurrentDeleteGPGKey :: Id
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
userCurrentDeleteGPGKey (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/gpg_keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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
UserCurrentDeleteGPGKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentDeleteGPGKey MimeNoContent 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 UserCurrentDeleteGPGKey
instance Produces UserCurrentDeleteGPGKey MimeNoContent
userCurrentDeleteKey
:: Id
-> GiteaRequest UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
userCurrentDeleteKey :: Id
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
userCurrentDeleteKey (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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
UserCurrentDeleteKey MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentDeleteKey MimeNoContent 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 UserCurrentDeleteKey
instance Produces UserCurrentDeleteKey MimeNoContent
userCurrentDeleteStar
:: Owner
-> Repo
-> GiteaRequest UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
userCurrentDeleteStar :: Owner
-> Repo
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
userCurrentDeleteStar (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/starred/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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
UserCurrentDeleteStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentDeleteStar MimeNoContent 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 UserCurrentDeleteStar
instance Produces UserCurrentDeleteStar MimeNoContent
userCurrentGetGPGKey
:: Id
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
userCurrentGetGPGKey :: Id
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
userCurrentGetGPGKey (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/gpg_keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCurrentGetGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentGetGPGKey
instance Produces UserCurrentGetGPGKey MimeJSON
userCurrentGetKey
:: Id
-> GiteaRequest UserCurrentGetKey MimeNoContent PublicKey MimeJSON
userCurrentGetKey :: Id
-> GiteaRequest UserCurrentGetKey MimeNoContent PublicKey MimeJSON
userCurrentGetKey (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest UserCurrentGetKey MimeNoContent PublicKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/keys/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey MimeNoContent PublicKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCurrentGetKey MimeNoContent 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 UserCurrentGetKey
instance Produces UserCurrentGetKey MimeJSON
userCurrentListFollowers
:: GiteaRequest UserCurrentListFollowers MimeNoContent [User] MimeJSON
userCurrentListFollowers :: GiteaRequest UserCurrentListFollowers MimeNoContent [User] MimeJSON
userCurrentListFollowers =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListFollowers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/followers"]
GiteaRequest UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListFollowers 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 UserCurrentListFollowers
instance HasOptionalParam UserCurrentListFollowers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListFollowers contentType res accept
-> Page
-> GiteaRequest UserCurrentListFollowers contentType res accept
applyOptionalParam GiteaRequest UserCurrentListFollowers contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListFollowers contentType res accept
req GiteaRequest UserCurrentListFollowers contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListFollowers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListFollowers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListFollowers contentType res accept
-> Limit
-> GiteaRequest UserCurrentListFollowers contentType res accept
applyOptionalParam GiteaRequest UserCurrentListFollowers contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListFollowers contentType res accept
req GiteaRequest UserCurrentListFollowers contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListFollowers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListFollowers MimeJSON
userCurrentListFollowing
:: GiteaRequest UserCurrentListFollowing MimeNoContent [User] MimeJSON
userCurrentListFollowing :: GiteaRequest UserCurrentListFollowing MimeNoContent [User] MimeJSON
userCurrentListFollowing =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListFollowing MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/following"]
GiteaRequest UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListFollowing 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 UserCurrentListFollowing
instance HasOptionalParam UserCurrentListFollowing Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListFollowing contentType res accept
-> Page
-> GiteaRequest UserCurrentListFollowing contentType res accept
applyOptionalParam GiteaRequest UserCurrentListFollowing contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListFollowing contentType res accept
req GiteaRequest UserCurrentListFollowing contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListFollowing contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListFollowing Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListFollowing contentType res accept
-> Limit
-> GiteaRequest UserCurrentListFollowing contentType res accept
applyOptionalParam GiteaRequest UserCurrentListFollowing contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListFollowing contentType res accept
req GiteaRequest UserCurrentListFollowing contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListFollowing contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListFollowing MimeJSON
userCurrentListGPGKeys
:: GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
userCurrentListGPGKeys :: GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
userCurrentListGPGKeys =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/gpg_keys"]
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentListGPGKeys
instance HasOptionalParam UserCurrentListGPGKeys Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListGPGKeys contentType res accept
-> Page
-> GiteaRequest UserCurrentListGPGKeys contentType res accept
applyOptionalParam GiteaRequest UserCurrentListGPGKeys contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListGPGKeys contentType res accept
req GiteaRequest UserCurrentListGPGKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListGPGKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListGPGKeys Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListGPGKeys contentType res accept
-> Limit
-> GiteaRequest UserCurrentListGPGKeys contentType res accept
applyOptionalParam GiteaRequest UserCurrentListGPGKeys contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListGPGKeys contentType res accept
req GiteaRequest UserCurrentListGPGKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListGPGKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListGPGKeys MimeJSON
userCurrentListKeys
:: GiteaRequest UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
userCurrentListKeys :: GiteaRequest UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
userCurrentListKeys =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/keys"]
GiteaRequest UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListKeys MimeNoContent [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 UserCurrentListKeys
instance HasOptionalParam UserCurrentListKeys Fingerprint where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListKeys contentType res accept
-> Fingerprint
-> GiteaRequest UserCurrentListKeys contentType res accept
applyOptionalParam GiteaRequest UserCurrentListKeys contentType res accept
req (Fingerprint Text
xs) =
GiteaRequest UserCurrentListKeys contentType res accept
req GiteaRequest UserCurrentListKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fingerprint", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam UserCurrentListKeys Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListKeys contentType res accept
-> Page -> GiteaRequest UserCurrentListKeys contentType res accept
applyOptionalParam GiteaRequest UserCurrentListKeys contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListKeys contentType res accept
req GiteaRequest UserCurrentListKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListKeys Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListKeys contentType res accept
-> Limit -> GiteaRequest UserCurrentListKeys contentType res accept
applyOptionalParam GiteaRequest UserCurrentListKeys contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListKeys contentType res accept
req GiteaRequest UserCurrentListKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListKeys MimeJSON
userCurrentListRepos
:: GiteaRequest UserCurrentListRepos MimeNoContent [Repository] MimeJSON
userCurrentListRepos :: GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
userCurrentListRepos =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/repos"]
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentListRepos
instance HasOptionalParam UserCurrentListRepos Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListRepos contentType res accept
-> Page -> GiteaRequest UserCurrentListRepos contentType res accept
applyOptionalParam GiteaRequest UserCurrentListRepos contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListRepos contentType res accept
req GiteaRequest UserCurrentListRepos contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListRepos contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListRepos Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListRepos contentType res accept
-> Limit
-> GiteaRequest UserCurrentListRepos contentType res accept
applyOptionalParam GiteaRequest UserCurrentListRepos contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListRepos contentType res accept
req GiteaRequest UserCurrentListRepos contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListRepos contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListRepos MimeJSON
userCurrentListStarred
:: GiteaRequest UserCurrentListStarred MimeNoContent [Repository] MimeJSON
userCurrentListStarred :: GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
userCurrentListStarred =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/starred"]
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentListStarred
instance HasOptionalParam UserCurrentListStarred Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListStarred contentType res accept
-> Page
-> GiteaRequest UserCurrentListStarred contentType res accept
applyOptionalParam GiteaRequest UserCurrentListStarred contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListStarred contentType res accept
req GiteaRequest UserCurrentListStarred contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListStarred contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListStarred Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListStarred contentType res accept
-> Limit
-> GiteaRequest UserCurrentListStarred contentType res accept
applyOptionalParam GiteaRequest UserCurrentListStarred contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListStarred contentType res accept
req GiteaRequest UserCurrentListStarred contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListStarred contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListStarred MimeJSON
userCurrentListSubscriptions
:: GiteaRequest UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
userCurrentListSubscriptions :: GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
userCurrentListSubscriptions =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/subscriptions"]
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentListSubscriptions
instance HasOptionalParam UserCurrentListSubscriptions Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListSubscriptions contentType res accept
-> Page
-> GiteaRequest UserCurrentListSubscriptions contentType res accept
applyOptionalParam GiteaRequest UserCurrentListSubscriptions contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentListSubscriptions contentType res accept
req GiteaRequest UserCurrentListSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListSubscriptions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentListSubscriptions Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentListSubscriptions contentType res accept
-> Limit
-> GiteaRequest UserCurrentListSubscriptions contentType res accept
applyOptionalParam GiteaRequest UserCurrentListSubscriptions contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentListSubscriptions contentType res accept
req GiteaRequest UserCurrentListSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentListSubscriptions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserCurrentListSubscriptions MimeJSON
userCurrentPostGPGKey
:: (Consumes UserCurrentPostGPGKey MimeJSON)
=> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
userCurrentPostGPGKey :: Consumes UserCurrentPostGPGKey MimeJSON =>
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
userCurrentPostGPGKey =
Method
-> [ByteString]
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/gpg_keys"]
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCurrentPostGPGKey MimeJSON GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentPostGPGKey
instance HasBodyParam UserCurrentPostGPGKey CreateGPGKeyOption
instance Consumes UserCurrentPostGPGKey MimeJSON
instance Produces UserCurrentPostGPGKey MimeJSON
userCurrentPostKey
:: (Consumes UserCurrentPostKey MimeJSON)
=> GiteaRequest UserCurrentPostKey MimeJSON PublicKey MimeJSON
userCurrentPostKey :: Consumes UserCurrentPostKey MimeJSON =>
GiteaRequest UserCurrentPostKey MimeJSON PublicKey MimeJSON
userCurrentPostKey =
Method
-> [ByteString]
-> GiteaRequest UserCurrentPostKey MimeJSON PublicKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/keys"]
GiteaRequest UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey MimeJSON PublicKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserCurrentPostKey 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 UserCurrentPostKey
instance HasBodyParam UserCurrentPostKey CreateKeyOption
instance Consumes UserCurrentPostKey MimeJSON
instance Produces UserCurrentPostKey MimeJSON
userCurrentPutFollow
:: Username
-> GiteaRequest UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
userCurrentPutFollow :: Username
-> GiteaRequest
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
userCurrentPutFollow (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/user/following/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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
UserCurrentPutFollow MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentPutFollow MimeNoContent 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 UserCurrentPutFollow
instance Produces UserCurrentPutFollow MimeNoContent
userCurrentPutStar
:: Owner
-> Repo
-> GiteaRequest UserCurrentPutStar MimeNoContent NoContent MimeNoContent
userCurrentPutStar :: Owner
-> Repo
-> GiteaRequest
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
userCurrentPutStar (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/user/starred/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo]
GiteaRequest
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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
UserCurrentPutStar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentPutStar MimeNoContent 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 UserCurrentPutStar
instance Produces UserCurrentPutStar MimeNoContent
userCurrentTrackedTimes
:: GiteaRequest UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userCurrentTrackedTimes :: GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
userCurrentTrackedTimes =
Method
-> [ByteString]
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/times"]
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserCurrentTrackedTimes MimeNoContent [TrackedTime] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserCurrentTrackedTimes
instance HasOptionalParam UserCurrentTrackedTimes Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentTrackedTimes contentType res accept
-> Page
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
applyOptionalParam GiteaRequest UserCurrentTrackedTimes contentType res accept
req (Page Int
xs) =
GiteaRequest UserCurrentTrackedTimes contentType res accept
req GiteaRequest UserCurrentTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentTrackedTimes Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentTrackedTimes contentType res accept
-> Limit
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
applyOptionalParam GiteaRequest UserCurrentTrackedTimes contentType res accept
req (Limit Int
xs) =
GiteaRequest UserCurrentTrackedTimes contentType res accept
req GiteaRequest UserCurrentTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserCurrentTrackedTimes Since where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentTrackedTimes contentType res accept
-> Since
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
applyOptionalParam GiteaRequest UserCurrentTrackedTimes contentType res accept
req (Since DateTime
xs) =
GiteaRequest UserCurrentTrackedTimes contentType res accept
req GiteaRequest UserCurrentTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"since", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam UserCurrentTrackedTimes Before where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserCurrentTrackedTimes contentType res accept
-> Before
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
applyOptionalParam GiteaRequest UserCurrentTrackedTimes contentType res accept
req (Before DateTime
xs) =
GiteaRequest UserCurrentTrackedTimes contentType res accept
req GiteaRequest UserCurrentTrackedTimes contentType res accept
-> [QueryItem]
-> GiteaRequest UserCurrentTrackedTimes contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"before", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance Produces UserCurrentTrackedTimes MimeJSON
userDeleteAccessToken
:: Username
-> Token
-> GiteaRequest UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
userDeleteAccessToken :: Username
-> Token
-> GiteaRequest
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
userDeleteAccessToken (Username Text
username) (Token Text
token) =
Method
-> [ByteString]
-> GiteaRequest
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/tokens/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
token]
GiteaRequest
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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
UserDeleteAccessToken MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserDeleteAccessToken MimeNoContent 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 UserDeleteAccessToken
instance Produces UserDeleteAccessToken MimeNoContent
userDeleteAvatar
:: GiteaRequest UserDeleteAvatar MimeNoContent NoContent MimeNoContent
userDeleteAvatar :: GiteaRequest UserDeleteAvatar MimeNoContent NoContent MimeNoContent
userDeleteAvatar =
Method
-> [ByteString]
-> GiteaRequest
UserDeleteAvatar MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/avatar"]
GiteaRequest UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserDeleteAvatar MimeNoContent 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 UserDeleteAvatar
instance Produces UserDeleteAvatar MimeNoContent
userDeleteEmail
:: (Consumes UserDeleteEmail contentType)
=> ContentType contentType
-> GiteaRequest UserDeleteEmail contentType NoContent MimeNoContent
userDeleteEmail :: forall contentType.
Consumes UserDeleteEmail contentType =>
ContentType contentType
-> GiteaRequest UserDeleteEmail contentType NoContent MimeNoContent
userDeleteEmail ContentType contentType
_ =
Method
-> [ByteString]
-> GiteaRequest UserDeleteEmail contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/emails"]
GiteaRequest UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest UserDeleteEmail 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 UserDeleteEmail
instance HasBodyParam UserDeleteEmail DeleteEmailOption
instance Consumes UserDeleteEmail MimeJSON
instance Consumes UserDeleteEmail MimePlainText
instance Produces UserDeleteEmail MimeNoContent
userDeleteHook
:: Id
-> GiteaRequest UserDeleteHook MimeNoContent NoContent MimeNoContent
userDeleteHook :: Id
-> GiteaRequest
UserDeleteHook MimeNoContent NoContent MimeNoContent
userDeleteHook (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserDeleteHook MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserDeleteHook MimeNoContent 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 UserDeleteHook
instance Produces UserDeleteHook MimeNoContent
userDeleteOAuth2Application
:: Id
-> GiteaRequest UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
userDeleteOAuth2Application :: Id
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
userDeleteOAuth2Application (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/applications/oauth2/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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
UserDeleteOAuth2Application MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserDeleteOAuth2Application MimeNoContent 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 UserDeleteOAuth2Application
instance Produces UserDeleteOAuth2Application MimeNoContent
userEditHook
:: (Consumes UserEditHook MimeJSON)
=> Id
-> GiteaRequest UserEditHook MimeJSON Hook MimeJSON
userEditHook :: Consumes UserEditHook MimeJSON =>
Id -> GiteaRequest UserEditHook MimeJSON Hook MimeJSON
userEditHook (Id Integer
id) =
Method
-> [ByteString] -> GiteaRequest UserEditHook MimeJSON Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/user/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserEditHook 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 UserEditHook MimeJSON Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserEditHook 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 UserEditHook
instance HasBodyParam UserEditHook EditHookOption
instance Consumes UserEditHook MimeJSON
instance Produces UserEditHook MimeJSON
userGet
:: Username
-> GiteaRequest UserGet MimeNoContent User MimeJSON
userGet :: Username -> GiteaRequest UserGet MimeNoContent User MimeJSON
userGet (Username Text
username) =
Method
-> [ByteString] -> GiteaRequest UserGet MimeNoContent User MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserGet 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 UserGet MimeNoContent User MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserGet 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 UserGet
instance Produces UserGet MimeJSON
userGetCurrent
:: GiteaRequest UserGetCurrent MimeNoContent User MimeJSON
userGetCurrent :: GiteaRequest UserGetCurrent MimeNoContent User MimeJSON
userGetCurrent =
Method
-> [ByteString]
-> GiteaRequest UserGetCurrent MimeNoContent User MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user"]
GiteaRequest UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserGetCurrent 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 UserGetCurrent MimeNoContent User MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserGetCurrent 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 UserGetCurrent
instance Produces UserGetCurrent MimeJSON
userGetHeatmapData
:: Username
-> GiteaRequest UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
userGetHeatmapData :: Username
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
userGetHeatmapData (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/heatmap"]
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserGetHeatmapData MimeNoContent [UserHeatmapData] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserGetHeatmapData
instance Produces UserGetHeatmapData MimeJSON
userGetHook
:: Id
-> GiteaRequest UserGetHook MimeNoContent Hook MimeJSON
userGetHook :: Id -> GiteaRequest UserGetHook MimeNoContent Hook MimeJSON
userGetHook (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest UserGetHook MimeNoContent Hook MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/hooks/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserGetHook 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 UserGetHook MimeNoContent Hook MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserGetHook 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 UserGetHook
instance Produces UserGetHook MimeJSON
userGetOAuth2Application
:: Id
-> GiteaRequest UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
userGetOAuth2Application :: Id
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
userGetOAuth2Application (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/applications/oauth2/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserGetOAuth2Application MimeNoContent OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserGetOAuth2Application
instance Produces UserGetOAuth2Application MimeJSON
userGetOauth2Application
:: GiteaRequest UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
userGetOauth2Application :: GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
userGetOauth2Application =
Method
-> [ByteString]
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/applications/oauth2"]
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserGetOauth2Application MimeNoContent [OAuth2Application] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserGetOauth2Application
instance HasOptionalParam UserGetOauth2Application Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetOauth2Application contentType res accept
-> Page
-> GiteaRequest UserGetOauth2Application contentType res accept
applyOptionalParam GiteaRequest UserGetOauth2Application contentType res accept
req (Page Int
xs) =
GiteaRequest UserGetOauth2Application contentType res accept
req GiteaRequest UserGetOauth2Application contentType res accept
-> [QueryItem]
-> GiteaRequest UserGetOauth2Application contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserGetOauth2Application Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetOauth2Application contentType res accept
-> Limit
-> GiteaRequest UserGetOauth2Application contentType res accept
applyOptionalParam GiteaRequest UserGetOauth2Application contentType res accept
req (Limit Int
xs) =
GiteaRequest UserGetOauth2Application contentType res accept
req GiteaRequest UserGetOauth2Application contentType res accept
-> [QueryItem]
-> GiteaRequest UserGetOauth2Application contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserGetOauth2Application MimeJSON
userGetRunnerRegistrationToken
:: GiteaRequest UserGetRunnerRegistrationToken MimeNoContent NoContent MimeNoContent
userGetRunnerRegistrationToken :: GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
userGetRunnerRegistrationToken =
Method
-> [ByteString]
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/actions/runners/registration-token"]
GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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
UserGetRunnerRegistrationToken
MimeNoContent
NoContent
MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserGetRunnerRegistrationToken
MimeNoContent
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 UserGetRunnerRegistrationToken
instance Produces UserGetRunnerRegistrationToken MimeNoContent
userGetStopWatches
:: GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
userGetStopWatches :: GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
userGetStopWatches =
Method
-> [ByteString]
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/stopwatches"]
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserGetStopWatches MimeNoContent [StopWatch] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserGetStopWatches
instance HasOptionalParam UserGetStopWatches Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetStopWatches contentType res accept
-> Page -> GiteaRequest UserGetStopWatches contentType res accept
applyOptionalParam GiteaRequest UserGetStopWatches contentType res accept
req (Page Int
xs) =
GiteaRequest UserGetStopWatches contentType res accept
req GiteaRequest UserGetStopWatches contentType res accept
-> [QueryItem]
-> GiteaRequest UserGetStopWatches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserGetStopWatches Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetStopWatches contentType res accept
-> Limit -> GiteaRequest UserGetStopWatches contentType res accept
applyOptionalParam GiteaRequest UserGetStopWatches contentType res accept
req (Limit Int
xs) =
GiteaRequest UserGetStopWatches contentType res accept
req GiteaRequest UserGetStopWatches contentType res accept
-> [QueryItem]
-> GiteaRequest UserGetStopWatches contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserGetStopWatches MimeJSON
userGetTokens
:: Username
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
userGetTokens :: Username
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
userGetTokens (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/tokens"]
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserGetTokens MimeNoContent [AccessToken] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserGetTokens
instance HasOptionalParam UserGetTokens Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetTokens contentType res accept
-> Page -> GiteaRequest UserGetTokens contentType res accept
applyOptionalParam GiteaRequest UserGetTokens contentType res accept
req (Page Int
xs) =
GiteaRequest UserGetTokens contentType res accept
req GiteaRequest UserGetTokens contentType res accept
-> [QueryItem] -> GiteaRequest UserGetTokens contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserGetTokens Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserGetTokens contentType res accept
-> Limit -> GiteaRequest UserGetTokens contentType res accept
applyOptionalParam GiteaRequest UserGetTokens contentType res accept
req (Limit Int
xs) =
GiteaRequest UserGetTokens contentType res accept
req GiteaRequest UserGetTokens contentType res accept
-> [QueryItem] -> GiteaRequest UserGetTokens contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserGetTokens MimeJSON
userListActivityFeeds
:: Username
-> GiteaRequest UserListActivityFeeds MimeNoContent [Activity] MimeJSON
userListActivityFeeds :: Username
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
userListActivityFeeds (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/activities/feeds"]
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserListActivityFeeds MimeNoContent [Activity] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListActivityFeeds
instance HasOptionalParam UserListActivityFeeds OnlyPerformedBy where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListActivityFeeds contentType res accept
-> OnlyPerformedBy
-> GiteaRequest UserListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest UserListActivityFeeds contentType res accept
req (OnlyPerformedBy Bool
xs) =
GiteaRequest UserListActivityFeeds contentType res accept
req GiteaRequest UserListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest UserListActivityFeeds 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
"only-performed-by", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam UserListActivityFeeds ParamDate where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListActivityFeeds contentType res accept
-> ParamDate
-> GiteaRequest UserListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest UserListActivityFeeds contentType res accept
req (ParamDate Date
xs) =
GiteaRequest UserListActivityFeeds contentType res accept
req GiteaRequest UserListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest UserListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Date) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"date", Date -> Maybe Date
forall a. a -> Maybe a
Just Date
xs)
instance HasOptionalParam UserListActivityFeeds Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListActivityFeeds contentType res accept
-> Page
-> GiteaRequest UserListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest UserListActivityFeeds contentType res accept
req (Page Int
xs) =
GiteaRequest UserListActivityFeeds contentType res accept
req GiteaRequest UserListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest UserListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListActivityFeeds Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListActivityFeeds contentType res accept
-> Limit
-> GiteaRequest UserListActivityFeeds contentType res accept
applyOptionalParam GiteaRequest UserListActivityFeeds contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListActivityFeeds contentType res accept
req GiteaRequest UserListActivityFeeds contentType res accept
-> [QueryItem]
-> GiteaRequest UserListActivityFeeds contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListActivityFeeds MimeJSON
userListBlocks
:: GiteaRequest UserListBlocks MimeNoContent [User] MimeJSON
userListBlocks :: GiteaRequest UserListBlocks MimeNoContent [User] MimeJSON
userListBlocks =
Method
-> [ByteString]
-> GiteaRequest UserListBlocks MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/blocks"]
GiteaRequest UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListBlocks 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 UserListBlocks MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListBlocks 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 UserListBlocks
instance HasOptionalParam UserListBlocks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListBlocks contentType res accept
-> Page -> GiteaRequest UserListBlocks contentType res accept
applyOptionalParam GiteaRequest UserListBlocks contentType res accept
req (Page Int
xs) =
GiteaRequest UserListBlocks contentType res accept
req GiteaRequest UserListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest UserListBlocks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListBlocks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListBlocks contentType res accept
-> Limit -> GiteaRequest UserListBlocks contentType res accept
applyOptionalParam GiteaRequest UserListBlocks contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListBlocks contentType res accept
req GiteaRequest UserListBlocks contentType res accept
-> [QueryItem]
-> GiteaRequest UserListBlocks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListBlocks MimeJSON
userListEmails
:: GiteaRequest UserListEmails MimeNoContent [Email] MimeJSON
userListEmails :: GiteaRequest UserListEmails MimeNoContent [Email] MimeJSON
userListEmails =
Method
-> [ByteString]
-> GiteaRequest UserListEmails MimeNoContent [Email] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/emails"]
GiteaRequest UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListEmails 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 UserListEmails MimeNoContent [Email] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListEmails 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 UserListEmails
instance Produces UserListEmails MimeJSON
userListFollowers
:: Username
-> GiteaRequest UserListFollowers MimeNoContent [User] MimeJSON
userListFollowers :: Username
-> GiteaRequest UserListFollowers MimeNoContent [User] MimeJSON
userListFollowers (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListFollowers MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/followers"]
GiteaRequest UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListFollowers 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 UserListFollowers MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListFollowers 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 UserListFollowers
instance HasOptionalParam UserListFollowers Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListFollowers contentType res accept
-> Page -> GiteaRequest UserListFollowers contentType res accept
applyOptionalParam GiteaRequest UserListFollowers contentType res accept
req (Page Int
xs) =
GiteaRequest UserListFollowers contentType res accept
req GiteaRequest UserListFollowers contentType res accept
-> [QueryItem]
-> GiteaRequest UserListFollowers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListFollowers Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListFollowers contentType res accept
-> Limit -> GiteaRequest UserListFollowers contentType res accept
applyOptionalParam GiteaRequest UserListFollowers contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListFollowers contentType res accept
req GiteaRequest UserListFollowers contentType res accept
-> [QueryItem]
-> GiteaRequest UserListFollowers contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListFollowers MimeJSON
userListFollowing
:: Username
-> GiteaRequest UserListFollowing MimeNoContent [User] MimeJSON
userListFollowing :: Username
-> GiteaRequest UserListFollowing MimeNoContent [User] MimeJSON
userListFollowing (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListFollowing MimeNoContent [User] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/following"]
GiteaRequest UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListFollowing 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 UserListFollowing MimeNoContent [User] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListFollowing 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 UserListFollowing
instance HasOptionalParam UserListFollowing Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListFollowing contentType res accept
-> Page -> GiteaRequest UserListFollowing contentType res accept
applyOptionalParam GiteaRequest UserListFollowing contentType res accept
req (Page Int
xs) =
GiteaRequest UserListFollowing contentType res accept
req GiteaRequest UserListFollowing contentType res accept
-> [QueryItem]
-> GiteaRequest UserListFollowing contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListFollowing Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListFollowing contentType res accept
-> Limit -> GiteaRequest UserListFollowing contentType res accept
applyOptionalParam GiteaRequest UserListFollowing contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListFollowing contentType res accept
req GiteaRequest UserListFollowing contentType res accept
-> [QueryItem]
-> GiteaRequest UserListFollowing contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListFollowing MimeJSON
userListGPGKeys
:: Username
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
userListGPGKeys :: Username
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
userListGPGKeys (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/gpg_keys"]
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListGPGKeys MimeNoContent [GPGKey] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListGPGKeys
instance HasOptionalParam UserListGPGKeys Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListGPGKeys contentType res accept
-> Page -> GiteaRequest UserListGPGKeys contentType res accept
applyOptionalParam GiteaRequest UserListGPGKeys contentType res accept
req (Page Int
xs) =
GiteaRequest UserListGPGKeys contentType res accept
req GiteaRequest UserListGPGKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserListGPGKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListGPGKeys Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListGPGKeys contentType res accept
-> Limit -> GiteaRequest UserListGPGKeys contentType res accept
applyOptionalParam GiteaRequest UserListGPGKeys contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListGPGKeys contentType res accept
req GiteaRequest UserListGPGKeys contentType res accept
-> [QueryItem]
-> GiteaRequest UserListGPGKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListGPGKeys MimeJSON
userListHooks
:: GiteaRequest UserListHooks MimeNoContent [Hook] MimeJSON
userListHooks :: GiteaRequest UserListHooks MimeNoContent [Hook] MimeJSON
userListHooks =
Method
-> [ByteString]
-> GiteaRequest UserListHooks MimeNoContent [Hook] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/hooks"]
GiteaRequest UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListHooks 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 UserListHooks MimeNoContent [Hook] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListHooks 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 UserListHooks
instance HasOptionalParam UserListHooks Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListHooks contentType res accept
-> Page -> GiteaRequest UserListHooks contentType res accept
applyOptionalParam GiteaRequest UserListHooks contentType res accept
req (Page Int
xs) =
GiteaRequest UserListHooks contentType res accept
req GiteaRequest UserListHooks contentType res accept
-> [QueryItem] -> GiteaRequest UserListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListHooks Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListHooks contentType res accept
-> Limit -> GiteaRequest UserListHooks contentType res accept
applyOptionalParam GiteaRequest UserListHooks contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListHooks contentType res accept
req GiteaRequest UserListHooks contentType res accept
-> [QueryItem] -> GiteaRequest UserListHooks contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListHooks MimeJSON
userListKeys
:: Username
-> GiteaRequest UserListKeys MimeNoContent [PublicKey] MimeJSON
userListKeys :: Username
-> GiteaRequest UserListKeys MimeNoContent [PublicKey] MimeJSON
userListKeys (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListKeys MimeNoContent [PublicKey] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/keys"]
GiteaRequest UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys MimeNoContent [PublicKey] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListKeys MimeNoContent [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 UserListKeys
instance HasOptionalParam UserListKeys Fingerprint where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListKeys contentType res accept
-> Fingerprint -> GiteaRequest UserListKeys contentType res accept
applyOptionalParam GiteaRequest UserListKeys contentType res accept
req (Fingerprint Text
xs) =
GiteaRequest UserListKeys contentType res accept
req GiteaRequest UserListKeys contentType res accept
-> [QueryItem] -> GiteaRequest UserListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fingerprint", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam UserListKeys Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListKeys contentType res accept
-> Page -> GiteaRequest UserListKeys contentType res accept
applyOptionalParam GiteaRequest UserListKeys contentType res accept
req (Page Int
xs) =
GiteaRequest UserListKeys contentType res accept
req GiteaRequest UserListKeys contentType res accept
-> [QueryItem] -> GiteaRequest UserListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListKeys Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListKeys contentType res accept
-> Limit -> GiteaRequest UserListKeys contentType res accept
applyOptionalParam GiteaRequest UserListKeys contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListKeys contentType res accept
req GiteaRequest UserListKeys contentType res accept
-> [QueryItem] -> GiteaRequest UserListKeys contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListKeys MimeJSON
userListRepos
:: Username
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
userListRepos :: Username
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
userListRepos (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/repos"]
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListRepos MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListRepos
instance HasOptionalParam UserListRepos Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListRepos contentType res accept
-> Page -> GiteaRequest UserListRepos contentType res accept
applyOptionalParam GiteaRequest UserListRepos contentType res accept
req (Page Int
xs) =
GiteaRequest UserListRepos contentType res accept
req GiteaRequest UserListRepos contentType res accept
-> [QueryItem] -> GiteaRequest UserListRepos contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListRepos Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListRepos contentType res accept
-> Limit -> GiteaRequest UserListRepos contentType res accept
applyOptionalParam GiteaRequest UserListRepos contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListRepos contentType res accept
req GiteaRequest UserListRepos contentType res accept
-> [QueryItem] -> GiteaRequest UserListRepos contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListRepos MimeJSON
userListStarred
:: Username
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
userListStarred :: Username
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
userListStarred (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/starred"]
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListStarred MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListStarred
instance HasOptionalParam UserListStarred Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListStarred contentType res accept
-> Page -> GiteaRequest UserListStarred contentType res accept
applyOptionalParam GiteaRequest UserListStarred contentType res accept
req (Page Int
xs) =
GiteaRequest UserListStarred contentType res accept
req GiteaRequest UserListStarred contentType res accept
-> [QueryItem]
-> GiteaRequest UserListStarred contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListStarred Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListStarred contentType res accept
-> Limit -> GiteaRequest UserListStarred contentType res accept
applyOptionalParam GiteaRequest UserListStarred contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListStarred contentType res accept
req GiteaRequest UserListStarred contentType res accept
-> [QueryItem]
-> GiteaRequest UserListStarred contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListStarred MimeJSON
userListSubscriptions
:: Username
-> GiteaRequest UserListSubscriptions MimeNoContent [Repository] MimeJSON
userListSubscriptions :: Username
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
userListSubscriptions (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username,ByteString
"/subscriptions"]
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserListSubscriptions MimeNoContent [Repository] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListSubscriptions
instance HasOptionalParam UserListSubscriptions Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListSubscriptions contentType res accept
-> Page
-> GiteaRequest UserListSubscriptions contentType res accept
applyOptionalParam GiteaRequest UserListSubscriptions contentType res accept
req (Page Int
xs) =
GiteaRequest UserListSubscriptions contentType res accept
req GiteaRequest UserListSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest UserListSubscriptions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListSubscriptions Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListSubscriptions contentType res accept
-> Limit
-> GiteaRequest UserListSubscriptions contentType res accept
applyOptionalParam GiteaRequest UserListSubscriptions contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListSubscriptions contentType res accept
req GiteaRequest UserListSubscriptions contentType res accept
-> [QueryItem]
-> GiteaRequest UserListSubscriptions contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListSubscriptions MimeJSON
userListTeams
:: GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
userListTeams :: GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
userListTeams =
Method
-> [ByteString]
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/user/teams"]
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserListTeams MimeNoContent [Team] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserListTeams
instance HasOptionalParam UserListTeams Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListTeams contentType res accept
-> Page -> GiteaRequest UserListTeams contentType res accept
applyOptionalParam GiteaRequest UserListTeams contentType res accept
req (Page Int
xs) =
GiteaRequest UserListTeams contentType res accept
req GiteaRequest UserListTeams contentType res accept
-> [QueryItem] -> GiteaRequest UserListTeams contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserListTeams Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserListTeams contentType res accept
-> Limit -> GiteaRequest UserListTeams contentType res accept
applyOptionalParam GiteaRequest UserListTeams contentType res accept
req (Limit Int
xs) =
GiteaRequest UserListTeams contentType res accept
req GiteaRequest UserListTeams contentType res accept
-> [QueryItem] -> GiteaRequest UserListTeams contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserListTeams MimeJSON
userSearch
:: GiteaRequest UserSearch MimeNoContent UserSearch200Response MimeJSON
userSearch :: GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
userSearch =
Method
-> [ByteString]
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/users/search"]
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserSearch MimeNoContent UserSearch200Response MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserSearch
instance HasOptionalParam UserSearch Q where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserSearch contentType res accept
-> Q -> GiteaRequest UserSearch contentType res accept
applyOptionalParam GiteaRequest UserSearch contentType res accept
req (Q Text
xs) =
GiteaRequest UserSearch contentType res accept
req GiteaRequest UserSearch contentType res accept
-> [QueryItem] -> GiteaRequest UserSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"q", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam UserSearch Uid where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserSearch contentType res accept
-> Uid -> GiteaRequest UserSearch contentType res accept
applyOptionalParam GiteaRequest UserSearch contentType res accept
req (Uid Integer
xs) =
GiteaRequest UserSearch contentType res accept
req GiteaRequest UserSearch contentType res accept
-> [QueryItem] -> GiteaRequest UserSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Integer) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"uid", Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam UserSearch Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserSearch contentType res accept
-> Page -> GiteaRequest UserSearch contentType res accept
applyOptionalParam GiteaRequest UserSearch contentType res accept
req (Page Int
xs) =
GiteaRequest UserSearch contentType res accept
req GiteaRequest UserSearch contentType res accept
-> [QueryItem] -> GiteaRequest UserSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam UserSearch Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest UserSearch contentType res accept
-> Limit -> GiteaRequest UserSearch contentType res accept
applyOptionalParam GiteaRequest UserSearch contentType res accept
req (Limit Int
xs) =
GiteaRequest UserSearch contentType res accept
req GiteaRequest UserSearch contentType res accept
-> [QueryItem] -> GiteaRequest UserSearch contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance Produces UserSearch MimeJSON
userUnblockUser
:: Username
-> GiteaRequest UserUnblockUser MimeNoContent NoContent MimeNoContent
userUnblockUser :: Username
-> GiteaRequest
UserUnblockUser MimeNoContent NoContent MimeNoContent
userUnblockUser (Username Text
username) =
Method
-> [ByteString]
-> GiteaRequest
UserUnblockUser MimeNoContent NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/user/blocks/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
username]
GiteaRequest UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser MimeNoContent NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserUnblockUser MimeNoContent 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 UserUnblockUser
instance Produces UserUnblockUser MimeNoContent
userUpdateAvatar
:: (Consumes UserUpdateAvatar contentType)
=> ContentType contentType
-> GiteaRequest UserUpdateAvatar contentType NoContent MimeNoContent
userUpdateAvatar :: forall contentType.
Consumes UserUpdateAvatar contentType =>
ContentType contentType
-> GiteaRequest
UserUpdateAvatar contentType NoContent MimeNoContent
userUpdateAvatar ContentType contentType
_ =
Method
-> [ByteString]
-> GiteaRequest
UserUpdateAvatar contentType NoContent MimeNoContent
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/avatar"]
GiteaRequest UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar contentType NoContent MimeNoContent
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserUpdateAvatar 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 UserUpdateAvatar
instance HasBodyParam UserUpdateAvatar UpdateUserAvatarOption
instance Consumes UserUpdateAvatar MimeJSON
instance Consumes UserUpdateAvatar MimePlainText
instance Produces UserUpdateAvatar MimeNoContent
userUpdateOAuth2Application
:: (Consumes UserUpdateOAuth2Application contentType, MimeRender contentType CreateOAuth2ApplicationOptions)
=> ContentType contentType
-> CreateOAuth2ApplicationOptions
-> Id
-> GiteaRequest UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
userUpdateOAuth2Application :: forall contentType.
(Consumes UserUpdateOAuth2Application contentType,
MimeRender contentType CreateOAuth2ApplicationOptions) =>
ContentType contentType
-> CreateOAuth2ApplicationOptions
-> Id
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
userUpdateOAuth2Application ContentType contentType
_ CreateOAuth2ApplicationOptions
body (Id Integer
id) =
Method
-> [ByteString]
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/user/applications/oauth2/",Integer -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Integer
id]
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req 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
UserUpdateOAuth2Application contentType OAuth2Application MimeJSON
-> CreateOAuth2ApplicationOptions
-> GiteaRequest
UserUpdateOAuth2Application contentType OAuth2Application 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 UserUpdateOAuth2Application contentType,
MimeRender contentType CreateOAuth2ApplicationOptions) =>
GiteaRequest UserUpdateOAuth2Application contentType res accept
-> CreateOAuth2ApplicationOptions
-> GiteaRequest UserUpdateOAuth2Application contentType res accept
`setBodyParam` CreateOAuth2ApplicationOptions
body
data UserUpdateOAuth2Application
instance HasBodyParam UserUpdateOAuth2Application CreateOAuth2ApplicationOptions
instance Consumes UserUpdateOAuth2Application MimeJSON
instance Consumes UserUpdateOAuth2Application MimePlainText
instance Produces UserUpdateOAuth2Application MimeJSON
userVerifyGPGKey
:: GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
userVerifyGPGKey :: GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
userVerifyGPGKey =
Method
-> [ByteString]
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/user/gpg_key_verify"]
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest UserVerifyGPGKey MimeNoContent GPGKey MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data UserVerifyGPGKey
instance Produces UserVerifyGPGKey MimeJSON