{-
   Gitea API.

   This documentation describes the Gitea API.

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

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

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

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

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

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

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

-- * Operations


-- ** Miscellaneous

-- *** getNodeInfo

-- | @GET \/nodeinfo@
-- 
-- Returns the nodeinfo of the Gitea application
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getNodeInfo
  :: GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
getNodeInfo :: GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
getNodeInfo =
  Method
-> [ByteString]
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/nodeinfo"]
    GiteaRequest GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo MimeNoContent NodeInfo MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetNodeInfo MimeNoContent NodeInfo 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 GetNodeInfo  
-- | @application/json@
instance Produces GetNodeInfo MimeJSON


-- *** getSigningKey

-- | @GET \/signing-key.gpg@
-- 
-- Get default signing-key.gpg
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getSigningKey
  :: GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
getSigningKey :: GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
getSigningKey =
  Method
-> [ByteString]
-> GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/signing-key.gpg"]
    GiteaRequest GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetSigningKey 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 GetSigningKey MimeNoContent Text MimePlainText
-> Proxy AuthApiKeyToken
-> GiteaRequest GetSigningKey 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 GetSigningKey  
-- | @text/plain@
instance Produces GetSigningKey MimePlainText


-- *** getVersion

-- | @GET \/version@
-- 
-- Returns the version of the Gitea application
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
getVersion
  :: GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
getVersion :: GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
getVersion =
  Method
-> [ByteString]
-> GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/version"]
    GiteaRequest GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthBasicBasicAuth
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeySudoParam
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion MimeNoContent ServerVersion MimeJSON
-> Proxy AuthApiKeyToken
-> GiteaRequest GetVersion MimeNoContent ServerVersion 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 GetVersion  
-- | @application/json@
instance Produces GetVersion MimeJSON


-- *** renderMarkdown

-- | @POST \/markdown@
-- 
-- Render a markdown document as HTML
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
renderMarkdown
  :: (Consumes RenderMarkdown MimeJSON)
  => GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
renderMarkdown :: Consumes RenderMarkdown MimeJSON =>
GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
renderMarkdown =
  Method
-> [ByteString]
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/markdown"]
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
-> Proxy AuthApiKeyToken
-> GiteaRequest RenderMarkdown MimeJSON Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyToken)

data RenderMarkdown 
instance HasBodyParam RenderMarkdown MarkdownOption 

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

-- | @text/html@
instance Produces RenderMarkdown MimeTextHtml


-- *** renderMarkdownRaw

-- | @POST \/markdown\/raw@
-- 
-- Render raw markdown as HTML
-- 
-- AuthMethod: 'AuthApiKeyTOTPHeader', 'AuthApiKeyAuthorizationHeaderToken', 'AuthApiKeySudoHeader', 'AuthBasicBasicAuth', 'AuthApiKeyAccessToken', 'AuthApiKeySudoParam', 'AuthApiKeyToken'
-- 
renderMarkdownRaw
  :: (Consumes RenderMarkdownRaw MimePlainText, MimeRender MimePlainText Body)
  => Body -- ^ "body" -  Request body to render
  -> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
renderMarkdownRaw :: (Consumes RenderMarkdownRaw MimePlainText,
 MimeRender MimePlainText Body) =>
Body
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
renderMarkdownRaw Body
body =
  Method
-> [ByteString]
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall req contentType res accept.
Method -> [ByteString] -> GiteaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/markdown/raw"]
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyTOTPHeader
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyTOTPHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyTOTPHeader)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyAuthorizationHeaderToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAuthorizationHeaderToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAuthorizationHeaderToken)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeySudoHeader
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoHeader
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoHeader)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthBasicBasicAuth
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthBasicBasicAuth
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasicAuth)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyAccessToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyAccessToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyAccessToken)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeySudoParam
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req contentType res accept
-> Proxy authMethod -> GiteaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeySudoParam
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeySudoParam)
    GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Proxy AuthApiKeyToken
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
forall authMethod req contentType res accept.
AuthMethod authMethod =>
GiteaRequest req 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 RenderMarkdownRaw MimePlainText Text MimeTextHtml
-> Body
-> GiteaRequest RenderMarkdownRaw MimePlainText Text MimeTextHtml
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 RenderMarkdownRaw contentType,
 MimeRender contentType Body) =>
GiteaRequest RenderMarkdownRaw contentType res accept
-> Body -> GiteaRequest RenderMarkdownRaw contentType res accept
`setBodyParam` Body
body

data RenderMarkdownRaw 

-- | /Body Param/ "body" - Request body to render
instance HasBodyParam RenderMarkdownRaw Body 

-- | @text/plain@
instance Consumes RenderMarkdownRaw MimePlainText

-- | @text/html@
instance Produces RenderMarkdownRaw MimeTextHtml