{-# 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.Notification 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
notifyGetList
:: GiteaRequest NotifyGetList MimeNoContent [NotificationThread] MimeJSON
notifyGetList :: GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
notifyGetList =
Method
-> [ByteString]
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/notifications"]
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyGetList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyGetList
instance HasOptionalParam NotifyGetList All where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> All -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (All Bool
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList 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
"all", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam NotifyGetList StatusTypes where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> StatusTypes -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (StatusTypes [Text]
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Text]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"status-types", [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs)
instance HasOptionalParam NotifyGetList SubjectType where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> SubjectType -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (SubjectType [E'SubjectType]
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [E'SubjectType]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"subject-type", [E'SubjectType] -> Maybe [E'SubjectType]
forall a. a -> Maybe a
Just [E'SubjectType]
xs)
instance HasOptionalParam NotifyGetList Since where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> Since -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (Since DateTime
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList 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 NotifyGetList Before where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> Before -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (Before DateTime
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"before", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam NotifyGetList Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> Page -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (Page Int
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList 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 NotifyGetList Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetList contentType res accept
-> Limit -> GiteaRequest NotifyGetList contentType res accept
applyOptionalParam GiteaRequest NotifyGetList contentType res accept
req (Limit Int
xs) =
GiteaRequest NotifyGetList contentType res accept
req GiteaRequest NotifyGetList contentType res accept
-> [QueryItem] -> GiteaRequest NotifyGetList 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 NotifyGetList MimeJSON
notifyGetRepoList
:: Owner
-> Repo
-> GiteaRequest NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
notifyGetRepoList :: Owner
-> Repo
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
notifyGetRepoList (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/notifications"]
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyGetRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyGetRepoList
instance HasOptionalParam NotifyGetRepoList All where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> All -> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (All Bool
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList 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
"all", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam NotifyGetRepoList StatusTypes where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> StatusTypes
-> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (StatusTypes [Text]
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Text]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"status-types", [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs)
instance HasOptionalParam NotifyGetRepoList SubjectType where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> SubjectType
-> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (SubjectType [E'SubjectType]
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [E'SubjectType]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"subject-type", [E'SubjectType] -> Maybe [E'SubjectType]
forall a. a -> Maybe a
Just [E'SubjectType]
xs)
instance HasOptionalParam NotifyGetRepoList Since where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> Since -> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (Since DateTime
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList 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 NotifyGetRepoList Before where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> Before -> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (Before DateTime
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` (Method, Maybe DateTime) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"before", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam NotifyGetRepoList Page where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> Page -> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (Page Int
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList 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 NotifyGetRepoList Limit where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyGetRepoList contentType res accept
-> Limit -> GiteaRequest NotifyGetRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyGetRepoList contentType res accept
req (Limit Int
xs) =
GiteaRequest NotifyGetRepoList contentType res accept
req GiteaRequest NotifyGetRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyGetRepoList 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 NotifyGetRepoList MimeJSON
notifyGetThread
:: IdText
-> GiteaRequest NotifyGetThread MimeNoContent NotificationThread MimeJSON
notifyGetThread :: IdText
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
notifyGetThread (IdText Text
id) =
Method
-> [ByteString]
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/notifications/threads/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyGetThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyGetThread
instance Produces NotifyGetThread MimeJSON
notifyNewAvailable
:: Accept accept
-> GiteaRequest NotifyNewAvailable MimeNoContent NotificationCount accept
notifyNewAvailable :: forall accept.
Accept accept
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
notifyNewAvailable Accept accept
_ =
Method
-> [ByteString]
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/notifications/new"]
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyNewAvailable MimeNoContent NotificationCount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyNewAvailable
instance Produces NotifyNewAvailable MimeTextHtml
instance Produces NotifyNewAvailable MimeJSON
notifyReadList
:: GiteaRequest NotifyReadList MimeNoContent [NotificationThread] MimeJSON
notifyReadList :: GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
notifyReadList =
Method
-> [ByteString]
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/notifications"]
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyReadList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyReadList
instance HasOptionalParam NotifyReadList LastReadAt where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadList contentType res accept
-> LastReadAt -> GiteaRequest NotifyReadList contentType res accept
applyOptionalParam GiteaRequest NotifyReadList contentType res accept
req (LastReadAt DateTime
xs) =
GiteaRequest NotifyReadList contentType res accept
req GiteaRequest NotifyReadList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadList 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
"last_read_at", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance HasOptionalParam NotifyReadList AllText where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadList contentType res accept
-> AllText -> GiteaRequest NotifyReadList contentType res accept
applyOptionalParam GiteaRequest NotifyReadList contentType res accept
req (AllText Text
xs) =
GiteaRequest NotifyReadList contentType res accept
req GiteaRequest NotifyReadList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadList 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
"all", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam NotifyReadList StatusTypes where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadList contentType res accept
-> StatusTypes
-> GiteaRequest NotifyReadList contentType res accept
applyOptionalParam GiteaRequest NotifyReadList contentType res accept
req (StatusTypes [Text]
xs) =
GiteaRequest NotifyReadList contentType res accept
req GiteaRequest NotifyReadList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Text]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"status-types", [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs)
instance HasOptionalParam NotifyReadList ToStatus where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadList contentType res accept
-> ToStatus -> GiteaRequest NotifyReadList contentType res accept
applyOptionalParam GiteaRequest NotifyReadList contentType res accept
req (ToStatus Text
xs) =
GiteaRequest NotifyReadList contentType res accept
req GiteaRequest NotifyReadList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadList 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
"to-status", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces NotifyReadList MimeJSON
notifyReadRepoList
:: Owner
-> Repo
-> GiteaRequest NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
notifyReadRepoList :: Owner
-> Repo
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
notifyReadRepoList (Owner Text
owner) (Repo Text
repo) =
Method
-> [ByteString]
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/repos/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
owner,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
repo,ByteString
"/notifications"]
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyReadRepoList MimeNoContent [NotificationThread] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyReadRepoList
instance HasOptionalParam NotifyReadRepoList AllText where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadRepoList contentType res accept
-> AllText
-> GiteaRequest NotifyReadRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyReadRepoList contentType res accept
req (AllText Text
xs) =
GiteaRequest NotifyReadRepoList contentType res accept
req GiteaRequest NotifyReadRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadRepoList 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
"all", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam NotifyReadRepoList StatusTypes where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadRepoList contentType res accept
-> StatusTypes
-> GiteaRequest NotifyReadRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyReadRepoList contentType res accept
req (StatusTypes [Text]
xs) =
GiteaRequest NotifyReadRepoList contentType res accept
req GiteaRequest NotifyReadRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadRepoList contentType res accept
forall req contentType res accept.
GiteaRequest req contentType res accept
-> [QueryItem] -> GiteaRequest req contentType res accept
`addQuery` CollectionFormat -> (Method, Maybe [Text]) -> [QueryItem]
forall a.
ToHttpApiData a =>
CollectionFormat -> (Method, Maybe [a]) -> [QueryItem]
toQueryColl CollectionFormat
MultiParamArray (Method
"status-types", [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs)
instance HasOptionalParam NotifyReadRepoList ToStatus where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadRepoList contentType res accept
-> ToStatus
-> GiteaRequest NotifyReadRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyReadRepoList contentType res accept
req (ToStatus Text
xs) =
GiteaRequest NotifyReadRepoList contentType res accept
req GiteaRequest NotifyReadRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadRepoList 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
"to-status", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam NotifyReadRepoList LastReadAt where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadRepoList contentType res accept
-> LastReadAt
-> GiteaRequest NotifyReadRepoList contentType res accept
applyOptionalParam GiteaRequest NotifyReadRepoList contentType res accept
req (LastReadAt DateTime
xs) =
GiteaRequest NotifyReadRepoList contentType res accept
req GiteaRequest NotifyReadRepoList contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadRepoList 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
"last_read_at", DateTime -> Maybe DateTime
forall a. a -> Maybe a
Just DateTime
xs)
instance Produces NotifyReadRepoList MimeJSON
notifyReadThread
:: IdText
-> GiteaRequest NotifyReadThread MimeNoContent NotificationThread MimeJSON
notifyReadThread :: IdText
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
notifyReadThread (IdText Text
id) =
Method
-> [ByteString]
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/notifications/threads/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest
NotifyReadThread MimeNoContent NotificationThread MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)
data NotifyReadThread
instance HasOptionalParam NotifyReadThread ToStatus where
applyOptionalParam :: forall contentType res accept.
GiteaRequest NotifyReadThread contentType res accept
-> ToStatus -> GiteaRequest NotifyReadThread contentType res accept
applyOptionalParam GiteaRequest NotifyReadThread contentType res accept
req (ToStatus Text
xs) =
GiteaRequest NotifyReadThread contentType res accept
req GiteaRequest NotifyReadThread contentType res accept
-> [QueryItem]
-> GiteaRequest NotifyReadThread 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
"to-status", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance Produces NotifyReadThread MimeJSON