{-
   Kubernetes

   No description provided (generated by Openapi Generator https://github.com/openapitools/openapi-generator)

   OpenAPI Version: 3.0.1
   Kubernetes API version: release-1.32
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Kubernetes.OpenAPI.API.CoreV1
-}

{-# 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 Kubernetes.OpenAPI.API.CoreV1 where

import Kubernetes.OpenAPI.Core
import Kubernetes.OpenAPI.MimeTypes
import Kubernetes.OpenAPI.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


-- ** CoreV1

-- *** connectDeleteNamespacedPodProxy

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect DELETE requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
connectDeleteNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
connectDeleteNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectDeleteNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectDeleteNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectDeleteNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectDeleteNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectDeleteNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNamespacedPodProxy mtype


-- *** connectDeleteNamespacedPodProxyWithPath

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect DELETE requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectDeleteNamespacedPodProxyWithPath MimeNoContent Text accept
connectDeleteNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxyWithPath MimeNoContent Text accept
connectDeleteNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectDeleteNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectDeleteNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectDeleteNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectDeleteNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectDeleteNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectDeleteNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNamespacedPodProxyWithPath mtype


-- *** connectDeleteNamespacedServiceProxy

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect DELETE requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectDeleteNamespacedServiceProxy MimeNoContent Text accept
connectDeleteNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxy MimeNoContent Text accept
connectDeleteNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectDeleteNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectDeleteNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectDeleteNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectDeleteNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectDeleteNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectDeleteNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNamespacedServiceProxy mtype


-- *** connectDeleteNamespacedServiceProxyWithPath

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect DELETE requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectDeleteNamespacedServiceProxyWithPath MimeNoContent Text accept
connectDeleteNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
connectDeleteNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectDeleteNamespacedServiceProxyWithPath
  MimeNoContent
  Text
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectDeleteNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectDeleteNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNamespacedServiceProxyWithPath mtype


-- *** connectDeleteNodeProxy

-- | @DELETE \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect DELETE requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectDeleteNodeProxy MimeNoContent Text accept
connectDeleteNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ConnectDeleteNodeProxy MimeNoContent Text accept
connectDeleteNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectDeleteNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectDeleteNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectDeleteNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectDeleteNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectDeleteNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectDeleteNodeProxy contentType res accept
req KubernetesRequest ConnectDeleteNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectDeleteNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNodeProxy mtype


-- *** connectDeleteNodeProxyWithPath

-- | @DELETE \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect DELETE requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectDeleteNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectDeleteNodeProxyWithPath MimeNoContent Text accept
connectDeleteNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectDeleteNodeProxyWithPath MimeNoContent Text accept
connectDeleteNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectDeleteNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectDeleteNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectDeleteNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectDeleteNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectDeleteNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectDeleteNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectDeleteNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectDeleteNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectDeleteNodeProxyWithPath mtype


-- *** connectGetNamespacedPodAttach

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/attach@
-- 
-- connect GET requests to attach of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedPodAttach
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodAttachOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectGetNamespacedPodAttach MimeNoContent Text accept
connectGetNamespacedPodAttach :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectGetNamespacedPodAttach MimeNoContent Text accept
connectGetNamespacedPodAttach  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/attach"]
    KubernetesRequest
  ConnectGetNamespacedPodAttach MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedPodAttach MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedPodAttach  

-- | /Optional Param/ "container" - The container in which to execute the command. Defaults to only container if there is only one container in the pod.
instance HasOptionalParam ConnectGetNamespacedPodAttach Container where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> Container
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req (Container Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"container", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "stderr" - Stderr if true indicates that stderr is to be redirected for the attach call. Defaults to true.
instance HasOptionalParam ConnectGetNamespacedPodAttach Stderr where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> Stderr
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req (Stderr Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stderr", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdin" - Stdin if true, redirects the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectGetNamespacedPodAttach Stdin where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> Stdin
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req (Stdin Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdin", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdout" - Stdout if true indicates that stdout is to be redirected for the attach call. Defaults to true.
instance HasOptionalParam ConnectGetNamespacedPodAttach Stdout where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> Stdout
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req (Stdout Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdout", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "tty" - TTY if true indicates that a tty will be allocated for the attach call. This is passed through the container runtime so the tty is allocated on the worker node by the container runtime. Defaults to false.
instance HasOptionalParam ConnectGetNamespacedPodAttach Tty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> Tty
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req (Tty Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"tty", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedPodAttach mtype


-- *** connectGetNamespacedPodExec

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/exec@
-- 
-- connect GET requests to exec of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedPodExec
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodExecOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectGetNamespacedPodExec MimeNoContent Text accept
connectGetNamespacedPodExec :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectGetNamespacedPodExec MimeNoContent Text accept
connectGetNamespacedPodExec  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedPodExec MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/exec"]
    KubernetesRequest
  ConnectGetNamespacedPodExec MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedPodExec MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedPodExec  

-- | /Optional Param/ "command" - Command is the remote command to execute. argv array. Not executed within a shell.
instance HasOptionalParam ConnectGetNamespacedPodExec Command where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Command
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Command Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"command", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "container" - Container in which to execute the command. Defaults to only container if there is only one container in the pod.
instance HasOptionalParam ConnectGetNamespacedPodExec Container where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Container
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Container Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"container", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "stderr" - Redirect the standard error stream of the pod for this call.
instance HasOptionalParam ConnectGetNamespacedPodExec Stderr where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Stderr
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Stderr Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stderr", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectGetNamespacedPodExec Stdin where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Stdin
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Stdin Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdin", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdout" - Redirect the standard output stream of the pod for this call.
instance HasOptionalParam ConnectGetNamespacedPodExec Stdout where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Stdout
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Stdout Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdout", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "tty" - TTY if true indicates that a tty will be allocated for the exec call. Defaults to false.
instance HasOptionalParam ConnectGetNamespacedPodExec Tty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> Tty
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req (Tty Bool
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"tty", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedPodExec mtype


-- *** connectGetNamespacedPodPortforward

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/portforward@
-- 
-- connect GET requests to portforward of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedPodPortforward
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodPortForwardOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectGetNamespacedPodPortforward MimeNoContent Text accept
connectGetNamespacedPodPortforward :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectGetNamespacedPodPortforward MimeNoContent Text accept
connectGetNamespacedPodPortforward  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedPodPortforward MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/portforward"]
    KubernetesRequest
  ConnectGetNamespacedPodPortforward MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedPodPortforward MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedPodPortforward  

-- | /Optional Param/ "ports" - List of ports to forward Required when using WebSockets
instance HasOptionalParam ConnectGetNamespacedPodPortforward Ports where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodPortforward contentType res accept
-> Ports
-> KubernetesRequest
     ConnectGetNamespacedPodPortforward contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodPortforward contentType res accept
req (Ports Int
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodPortforward contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodPortforward contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodPortforward contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ports", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedPodPortforward mtype


-- *** connectGetNamespacedPodProxy

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect GET requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectGetNamespacedPodProxy MimeNoContent Text accept
connectGetNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectGetNamespacedPodProxy MimeNoContent Text accept
connectGetNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectGetNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectGetNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectGetNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedPodProxy mtype


-- *** connectGetNamespacedPodProxyWithPath

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect GET requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectGetNamespacedPodProxyWithPath MimeNoContent Text accept
connectGetNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectGetNamespacedPodProxyWithPath MimeNoContent Text accept
connectGetNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectGetNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectGetNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectGetNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectGetNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedPodProxyWithPath mtype


-- *** connectGetNamespacedServiceProxy

-- | @GET \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect GET requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectGetNamespacedServiceProxy MimeNoContent Text accept
connectGetNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectGetNamespacedServiceProxy MimeNoContent Text accept
connectGetNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectGetNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectGetNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectGetNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectGetNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedServiceProxy mtype


-- *** connectGetNamespacedServiceProxyWithPath

-- | @GET \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect GET requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectGetNamespacedServiceProxyWithPath MimeNoContent Text accept
connectGetNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectGetNamespacedServiceProxyWithPath MimeNoContent Text accept
connectGetNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNamespacedServiceProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectGetNamespacedServiceProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNamespacedServiceProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectGetNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectGetNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectGetNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectGetNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNamespacedServiceProxyWithPath mtype


-- *** connectGetNodeProxy

-- | @GET \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect GET requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectGetNodeProxy MimeNoContent Text accept
connectGetNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ConnectGetNodeProxy MimeNoContent Text accept
connectGetNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ConnectGetNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectGetNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ConnectGetNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectGetNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectGetNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectGetNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectGetNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectGetNodeProxy contentType res accept
req KubernetesRequest ConnectGetNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectGetNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNodeProxy mtype


-- *** connectGetNodeProxyWithPath

-- | @GET \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect GET requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectGetNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectGetNodeProxyWithPath MimeNoContent Text accept
connectGetNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectGetNodeProxyWithPath MimeNoContent Text accept
connectGetNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectGetNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectGetNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectGetNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectGetNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectGetNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectGetNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectGetNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectGetNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectGetNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectGetNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectGetNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectGetNodeProxyWithPath mtype


-- *** connectHeadNamespacedPodProxy

-- | @HEAD \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect HEAD requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectHeadNamespacedPodProxy MimeNoContent Text accept
connectHeadNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectHeadNamespacedPodProxy MimeNoContent Text accept
connectHeadNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectHeadNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectHeadNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectHeadNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectHeadNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectHeadNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectHeadNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectHeadNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectHeadNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectHeadNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectHeadNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNamespacedPodProxy mtype


-- *** connectHeadNamespacedPodProxyWithPath

-- | @HEAD \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect HEAD requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectHeadNamespacedPodProxyWithPath MimeNoContent Text accept
connectHeadNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectHeadNamespacedPodProxyWithPath MimeNoContent Text accept
connectHeadNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectHeadNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectHeadNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectHeadNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectHeadNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectHeadNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectHeadNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectHeadNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectHeadNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectHeadNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectHeadNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNamespacedPodProxyWithPath mtype


-- *** connectHeadNamespacedServiceProxy

-- | @HEAD \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect HEAD requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectHeadNamespacedServiceProxy MimeNoContent Text accept
connectHeadNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxy MimeNoContent Text accept
connectHeadNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectHeadNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectHeadNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectHeadNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectHeadNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectHeadNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectHeadNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNamespacedServiceProxy mtype


-- *** connectHeadNamespacedServiceProxyWithPath

-- | @HEAD \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect HEAD requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectHeadNamespacedServiceProxyWithPath MimeNoContent Text accept
connectHeadNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxyWithPath MimeNoContent Text accept
connectHeadNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectHeadNamespacedServiceProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectHeadNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectHeadNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectHeadNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectHeadNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectHeadNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectHeadNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNamespacedServiceProxyWithPath mtype


-- *** connectHeadNodeProxy

-- | @HEAD \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect HEAD requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectHeadNodeProxy MimeNoContent Text accept
connectHeadNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ConnectHeadNodeProxy MimeNoContent Text accept
connectHeadNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ConnectHeadNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectHeadNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ConnectHeadNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectHeadNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectHeadNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectHeadNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectHeadNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectHeadNodeProxy contentType res accept
req KubernetesRequest ConnectHeadNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectHeadNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNodeProxy mtype


-- *** connectHeadNodeProxyWithPath

-- | @HEAD \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect HEAD requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectHeadNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectHeadNodeProxyWithPath MimeNoContent Text accept
connectHeadNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectHeadNodeProxyWithPath MimeNoContent Text accept
connectHeadNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectHeadNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"HEAD" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectHeadNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectHeadNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectHeadNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectHeadNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectHeadNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectHeadNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectHeadNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectHeadNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectHeadNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectHeadNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectHeadNodeProxyWithPath mtype


-- *** connectOptionsNamespacedPodProxy

-- | @OPTIONS \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect OPTIONS requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectOptionsNamespacedPodProxy MimeNoContent Text accept
connectOptionsNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxy MimeNoContent Text accept
connectOptionsNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectOptionsNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectOptionsNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectOptionsNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectOptionsNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectOptionsNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectOptionsNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNamespacedPodProxy mtype


-- *** connectOptionsNamespacedPodProxyWithPath

-- | @OPTIONS \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect OPTIONS requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectOptionsNamespacedPodProxyWithPath MimeNoContent Text accept
connectOptionsNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxyWithPath MimeNoContent Text accept
connectOptionsNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectOptionsNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectOptionsNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectOptionsNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectOptionsNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectOptionsNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectOptionsNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectOptionsNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNamespacedPodProxyWithPath mtype


-- *** connectOptionsNamespacedServiceProxy

-- | @OPTIONS \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect OPTIONS requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectOptionsNamespacedServiceProxy MimeNoContent Text accept
connectOptionsNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxy MimeNoContent Text accept
connectOptionsNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectOptionsNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectOptionsNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectOptionsNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectOptionsNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectOptionsNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectOptionsNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNamespacedServiceProxy mtype


-- *** connectOptionsNamespacedServiceProxyWithPath

-- | @OPTIONS \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect OPTIONS requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectOptionsNamespacedServiceProxyWithPath MimeNoContent Text accept
connectOptionsNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
connectOptionsNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectOptionsNamespacedServiceProxyWithPath
  MimeNoContent
  Text
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectOptionsNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectOptionsNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNamespacedServiceProxyWithPath mtype


-- *** connectOptionsNodeProxy

-- | @OPTIONS \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect OPTIONS requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectOptionsNodeProxy MimeNoContent Text accept
connectOptionsNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ConnectOptionsNodeProxy MimeNoContent Text accept
connectOptionsNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectOptionsNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectOptionsNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectOptionsNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectOptionsNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectOptionsNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectOptionsNodeProxy contentType res accept
req KubernetesRequest ConnectOptionsNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectOptionsNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNodeProxy mtype


-- *** connectOptionsNodeProxyWithPath

-- | @OPTIONS \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect OPTIONS requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectOptionsNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectOptionsNodeProxyWithPath MimeNoContent Text accept
connectOptionsNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectOptionsNodeProxyWithPath MimeNoContent Text accept
connectOptionsNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectOptionsNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"OPTIONS" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectOptionsNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectOptionsNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectOptionsNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectOptionsNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectOptionsNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectOptionsNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectOptionsNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectOptionsNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectOptionsNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectOptionsNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectOptionsNodeProxyWithPath mtype


-- *** connectPatchNamespacedPodProxy

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect PATCH requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPatchNamespacedPodProxy MimeNoContent Text accept
connectPatchNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPatchNamespacedPodProxy MimeNoContent Text accept
connectPatchNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPatchNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPatchNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPatchNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPatchNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPatchNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPatchNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectPatchNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPatchNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNamespacedPodProxy mtype


-- *** connectPatchNamespacedPodProxyWithPath

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect PATCH requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPatchNamespacedPodProxyWithPath MimeNoContent Text accept
connectPatchNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPatchNamespacedPodProxyWithPath MimeNoContent Text accept
connectPatchNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPatchNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPatchNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPatchNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPatchNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPatchNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPatchNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPatchNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPatchNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNamespacedPodProxyWithPath mtype


-- *** connectPatchNamespacedServiceProxy

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect PATCH requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPatchNamespacedServiceProxy MimeNoContent Text accept
connectPatchNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxy MimeNoContent Text accept
connectPatchNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPatchNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPatchNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPatchNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPatchNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPatchNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectPatchNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNamespacedServiceProxy mtype


-- *** connectPatchNamespacedServiceProxyWithPath

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect PATCH requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPatchNamespacedServiceProxyWithPath MimeNoContent Text accept
connectPatchNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
connectPatchNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPatchNamespacedServiceProxyWithPath
  MimeNoContent
  Text
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxyWithPath
     MimeNoContent
     Text
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPatchNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPatchNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPatchNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPatchNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPatchNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPatchNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNamespacedServiceProxyWithPath mtype


-- *** connectPatchNodeProxy

-- | @PATCH \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect PATCH requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectPatchNodeProxy MimeNoContent Text accept
connectPatchNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ConnectPatchNodeProxy MimeNoContent Text accept
connectPatchNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectPatchNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPatchNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectPatchNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectPatchNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectPatchNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectPatchNodeProxy contentType res accept
req KubernetesRequest ConnectPatchNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectPatchNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNodeProxy mtype


-- *** connectPatchNodeProxyWithPath

-- | @PATCH \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect PATCH requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPatchNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPatchNodeProxyWithPath MimeNoContent Text accept
connectPatchNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectPatchNodeProxyWithPath MimeNoContent Text accept
connectPatchNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPatchNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPatchNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPatchNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPatchNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPatchNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPatchNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPatchNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPatchNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPatchNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPatchNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPatchNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPatchNodeProxyWithPath mtype


-- *** connectPostNamespacedPodAttach

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/attach@
-- 
-- connect POST requests to attach of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedPodAttach
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodAttachOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPostNamespacedPodAttach MimeNoContent Text accept
connectPostNamespacedPodAttach :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPostNamespacedPodAttach MimeNoContent Text accept
connectPostNamespacedPodAttach  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/attach"]
    KubernetesRequest
  ConnectPostNamespacedPodAttach MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedPodAttach MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedPodAttach  

-- | /Optional Param/ "container" - The container in which to execute the command. Defaults to only container if there is only one container in the pod.
instance HasOptionalParam ConnectPostNamespacedPodAttach Container where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> Container
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req (Container Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"container", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "stderr" - Stderr if true indicates that stderr is to be redirected for the attach call. Defaults to true.
instance HasOptionalParam ConnectPostNamespacedPodAttach Stderr where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> Stderr
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req (Stderr Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stderr", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdin" - Stdin if true, redirects the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectPostNamespacedPodAttach Stdin where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> Stdin
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req (Stdin Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdin", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdout" - Stdout if true indicates that stdout is to be redirected for the attach call. Defaults to true.
instance HasOptionalParam ConnectPostNamespacedPodAttach Stdout where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> Stdout
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req (Stdout Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdout", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "tty" - TTY if true indicates that a tty will be allocated for the attach call. This is passed through the container runtime so the tty is allocated on the worker node by the container runtime. Defaults to false.
instance HasOptionalParam ConnectPostNamespacedPodAttach Tty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> Tty
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req (Tty Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodAttach contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodAttach contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"tty", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedPodAttach mtype


-- *** connectPostNamespacedPodExec

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/exec@
-- 
-- connect POST requests to exec of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedPodExec
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodExecOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPostNamespacedPodExec MimeNoContent Text accept
connectPostNamespacedPodExec :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPostNamespacedPodExec MimeNoContent Text accept
connectPostNamespacedPodExec  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedPodExec MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/exec"]
    KubernetesRequest
  ConnectPostNamespacedPodExec MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedPodExec MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedPodExec  

-- | /Optional Param/ "command" - Command is the remote command to execute. argv array. Not executed within a shell.
instance HasOptionalParam ConnectPostNamespacedPodExec Command where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Command
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Command Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"command", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "container" - Container in which to execute the command. Defaults to only container if there is only one container in the pod.
instance HasOptionalParam ConnectPostNamespacedPodExec Container where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Container
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Container Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"container", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "stderr" - Redirect the standard error stream of the pod for this call.
instance HasOptionalParam ConnectPostNamespacedPodExec Stderr where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Stderr
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Stderr Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stderr", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectPostNamespacedPodExec Stdin where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Stdin
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Stdin Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdin", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "stdout" - Redirect the standard output stream of the pod for this call.
instance HasOptionalParam ConnectPostNamespacedPodExec Stdout where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Stdout
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Stdout Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stdout", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "tty" - TTY if true indicates that a tty will be allocated for the exec call. Defaults to false.
instance HasOptionalParam ConnectPostNamespacedPodExec Tty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> Tty
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req (Tty Bool
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodExec contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodExec contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"tty", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedPodExec mtype


-- *** connectPostNamespacedPodPortforward

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/portforward@
-- 
-- connect POST requests to portforward of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedPodPortforward
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodPortForwardOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPostNamespacedPodPortforward MimeNoContent Text accept
connectPostNamespacedPodPortforward :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPostNamespacedPodPortforward MimeNoContent Text accept
connectPostNamespacedPodPortforward  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedPodPortforward MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/portforward"]
    KubernetesRequest
  ConnectPostNamespacedPodPortforward MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedPodPortforward MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedPodPortforward  

-- | /Optional Param/ "ports" - List of ports to forward Required when using WebSockets
instance HasOptionalParam ConnectPostNamespacedPodPortforward Ports where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodPortforward contentType res accept
-> Ports
-> KubernetesRequest
     ConnectPostNamespacedPodPortforward contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodPortforward contentType res accept
req (Ports Int
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodPortforward contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodPortforward contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodPortforward contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ports", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedPodPortforward mtype


-- *** connectPostNamespacedPodProxy

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect POST requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPostNamespacedPodProxy MimeNoContent Text accept
connectPostNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPostNamespacedPodProxy MimeNoContent Text accept
connectPostNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPostNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPostNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPostNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedPodProxy mtype


-- *** connectPostNamespacedPodProxyWithPath

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect POST requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPostNamespacedPodProxyWithPath MimeNoContent Text accept
connectPostNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPostNamespacedPodProxyWithPath MimeNoContent Text accept
connectPostNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPostNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPostNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPostNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPostNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedPodProxyWithPath mtype


-- *** connectPostNamespacedServiceProxy

-- | @POST \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect POST requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPostNamespacedServiceProxy MimeNoContent Text accept
connectPostNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPostNamespacedServiceProxy MimeNoContent Text accept
connectPostNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPostNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPostNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPostNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectPostNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedServiceProxy mtype


-- *** connectPostNamespacedServiceProxyWithPath

-- | @POST \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect POST requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPostNamespacedServiceProxyWithPath MimeNoContent Text accept
connectPostNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPostNamespacedServiceProxyWithPath MimeNoContent Text accept
connectPostNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNamespacedServiceProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPostNamespacedServiceProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNamespacedServiceProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPostNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPostNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPostNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPostNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNamespacedServiceProxyWithPath mtype


-- *** connectPostNodeProxy

-- | @POST \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect POST requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectPostNodeProxy MimeNoContent Text accept
connectPostNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ConnectPostNodeProxy MimeNoContent Text accept
connectPostNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ConnectPostNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectPostNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ConnectPostNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPostNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectPostNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectPostNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectPostNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectPostNodeProxy contentType res accept
req KubernetesRequest ConnectPostNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectPostNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNodeProxy mtype


-- *** connectPostNodeProxyWithPath

-- | @POST \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect POST requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPostNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPostNodeProxyWithPath MimeNoContent Text accept
connectPostNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectPostNodeProxyWithPath MimeNoContent Text accept
connectPostNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPostNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPostNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPostNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPostNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPostNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPostNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPostNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPostNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPostNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPostNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPostNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPostNodeProxyWithPath mtype


-- *** connectPutNamespacedPodProxy

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy@
-- 
-- connect PUT requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNamespacedPodProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPutNamespacedPodProxy MimeNoContent Text accept
connectPutNamespacedPodProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPutNamespacedPodProxy MimeNoContent Text accept
connectPutNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPutNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPutNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPutNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNamespacedPodProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPutNamespacedPodProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPutNamespacedPodProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPutNamespacedPodProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPutNamespacedPodProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPutNamespacedPodProxy contentType res accept
req KubernetesRequest
  ConnectPutNamespacedPodProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPutNamespacedPodProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNamespacedPodProxy mtype


-- *** connectPutNamespacedPodProxyWithPath

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/proxy\/{path}@
-- 
-- connect PUT requests to proxy of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNamespacedPodProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPutNamespacedPodProxyWithPath MimeNoContent Text accept
connectPutNamespacedPodProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPutNamespacedPodProxyWithPath MimeNoContent Text accept
connectPutNamespacedPodProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPutNamespacedPodProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPutNamespacedPodProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPutNamespacedPodProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNamespacedPodProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to pod.
instance HasOptionalParam ConnectPutNamespacedPodProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPutNamespacedPodProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPutNamespacedPodProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPutNamespacedPodProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPutNamespacedPodProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPutNamespacedPodProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPutNamespacedPodProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNamespacedPodProxyWithPath mtype


-- *** connectPutNamespacedServiceProxy

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy@
-- 
-- connect PUT requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNamespacedServiceProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ConnectPutNamespacedServiceProxy MimeNoContent Text accept
connectPutNamespacedServiceProxy :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectPutNamespacedServiceProxy MimeNoContent Text accept
connectPutNamespacedServiceProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPutNamespacedServiceProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectPutNamespacedServiceProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPutNamespacedServiceProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNamespacedServiceProxy  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPutNamespacedServiceProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPutNamespacedServiceProxy contentType res accept
-> Path
-> KubernetesRequest
     ConnectPutNamespacedServiceProxy contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPutNamespacedServiceProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest
  ConnectPutNamespacedServiceProxy contentType res accept
req KubernetesRequest
  ConnectPutNamespacedServiceProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPutNamespacedServiceProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNamespacedServiceProxy mtype


-- *** connectPutNamespacedServiceProxyWithPath

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/proxy\/{path}@
-- 
-- connect PUT requests to proxy of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNamespacedServiceProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceProxyOptions
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPutNamespacedServiceProxyWithPath MimeNoContent Text accept
connectPutNamespacedServiceProxyWithPath :: forall accept.
Accept accept
-> Name
-> Namespace
-> Path
-> KubernetesRequest
     ConnectPutNamespacedServiceProxyWithPath MimeNoContent Text accept
connectPutNamespacedServiceProxyWithPath  Accept accept
_ (Name Text
name) (Namespace Text
namespace) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPutNamespacedServiceProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPutNamespacedServiceProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPutNamespacedServiceProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNamespacedServiceProxyWithPath  

-- | /Optional Param/ "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy.
instance HasOptionalParam ConnectPutNamespacedServiceProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPutNamespacedServiceProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPutNamespacedServiceProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPutNamespacedServiceProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPutNamespacedServiceProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPutNamespacedServiceProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPutNamespacedServiceProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNamespacedServiceProxyWithPath mtype


-- *** connectPutNodeProxy

-- | @PUT \/api\/v1\/nodes\/{name}\/proxy@
-- 
-- connect PUT requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNodeProxy
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> KubernetesRequest ConnectPutNodeProxy MimeNoContent Text accept
connectPutNodeProxy :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ConnectPutNodeProxy MimeNoContent Text accept
connectPutNodeProxy  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ConnectPutNodeProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest ConnectPutNodeProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ConnectPutNodeProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNodeProxy  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPutNodeProxy Path where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ConnectPutNodeProxy contentType res accept
-> Path
-> KubernetesRequest ConnectPutNodeProxy contentType res accept
applyOptionalParam KubernetesRequest ConnectPutNodeProxy contentType res accept
req (Path Text
xs) =
    KubernetesRequest ConnectPutNodeProxy contentType res accept
req KubernetesRequest ConnectPutNodeProxy contentType res accept
-> [QueryItem]
-> KubernetesRequest ConnectPutNodeProxy contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNodeProxy mtype


-- *** connectPutNodeProxyWithPath

-- | @PUT \/api\/v1\/nodes\/{name}\/proxy\/{path}@
-- 
-- connect PUT requests to proxy of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
connectPutNodeProxyWithPath
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the NodeProxyOptions
  -> Path -- ^ "path" -  path to the resource
  -> KubernetesRequest ConnectPutNodeProxyWithPath MimeNoContent Text accept
connectPutNodeProxyWithPath :: forall accept.
Accept accept
-> Name
-> Path
-> KubernetesRequest
     ConnectPutNodeProxyWithPath MimeNoContent Text accept
connectPutNodeProxyWithPath  Accept accept
_ (Name Text
name) (Path Text
path) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectPutNodeProxyWithPath MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
path]
    KubernetesRequest
  ConnectPutNodeProxyWithPath MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectPutNodeProxyWithPath MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectPutNodeProxyWithPath  

-- | /Optional Param/ "path" - Path is the URL path to use for the current proxy request to node.
instance HasOptionalParam ConnectPutNodeProxyWithPath Path2 where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ConnectPutNodeProxyWithPath contentType res accept
-> Path2
-> KubernetesRequest
     ConnectPutNodeProxyWithPath contentType res accept
applyOptionalParam KubernetesRequest
  ConnectPutNodeProxyWithPath contentType res accept
req (Path2 Text
xs) =
    KubernetesRequest
  ConnectPutNodeProxyWithPath contentType res accept
req KubernetesRequest
  ConnectPutNodeProxyWithPath contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ConnectPutNodeProxyWithPath contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"path", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @*/*@
instance MimeType mtype => Produces ConnectPutNodeProxyWithPath mtype


-- *** createNamespace

-- | @POST \/api\/v1\/namespaces@
-- 
-- create a Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespace
  :: (Consumes CreateNamespace contentType, MimeRender contentType V1Namespace)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Namespace -- ^ "body"
  -> KubernetesRequest CreateNamespace contentType V1Namespace accept
createNamespace :: forall contentType accept.
(Consumes CreateNamespace contentType,
 MimeRender contentType V1Namespace) =>
ContentType contentType
-> Accept accept
-> V1Namespace
-> KubernetesRequest CreateNamespace contentType V1Namespace accept
createNamespace ContentType contentType
_  Accept accept
_ V1Namespace
body =
  Method
-> [ByteString]
-> KubernetesRequest CreateNamespace contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces"]
    KubernetesRequest CreateNamespace contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest CreateNamespace contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest CreateNamespace contentType V1Namespace accept
-> V1Namespace
-> KubernetesRequest CreateNamespace contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespace contentType,
 MimeRender contentType V1Namespace) =>
KubernetesRequest CreateNamespace contentType res accept
-> V1Namespace
-> KubernetesRequest CreateNamespace contentType res accept
`setBodyParam` V1Namespace
body

data CreateNamespace 
instance HasBodyParam CreateNamespace V1Namespace 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespace contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespace DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespace contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespace FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespace contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespace FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespace contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespace mtype

-- | @application/json@
instance Produces CreateNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespace MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespace MimeCbor
-- | @application/yaml@
instance Produces CreateNamespace MimeYaml


-- *** createNamespacedBinding

-- | @POST \/api\/v1\/namespaces\/{namespace}\/bindings@
-- 
-- create a Binding
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedBinding
  :: (Consumes CreateNamespacedBinding contentType, MimeRender contentType V1Binding)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Binding -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedBinding contentType V1Binding accept
createNamespacedBinding :: forall contentType accept.
(Consumes CreateNamespacedBinding contentType,
 MimeRender contentType V1Binding) =>
ContentType contentType
-> Accept accept
-> V1Binding
-> Namespace
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
createNamespacedBinding ContentType contentType
_  Accept accept
_ V1Binding
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/bindings"]
    KubernetesRequest
  CreateNamespacedBinding contentType V1Binding accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedBinding contentType V1Binding accept
-> V1Binding
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedBinding contentType,
 MimeRender contentType V1Binding) =>
KubernetesRequest CreateNamespacedBinding contentType res accept
-> V1Binding
-> KubernetesRequest CreateNamespacedBinding contentType res accept
`setBodyParam` V1Binding
body

data CreateNamespacedBinding 
instance HasBodyParam CreateNamespacedBinding V1Binding 

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedBinding DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedBinding contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespacedBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedBinding contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedBinding contentType res accept
req KubernetesRequest CreateNamespacedBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedBinding FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedBinding contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedBinding contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedBinding contentType res accept
req KubernetesRequest CreateNamespacedBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedBinding FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedBinding contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespacedBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedBinding contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedBinding contentType res accept
req KubernetesRequest CreateNamespacedBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedBinding Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedBinding contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedBinding contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedBinding contentType res accept
req KubernetesRequest CreateNamespacedBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedBinding mtype

-- | @application/json@
instance Produces CreateNamespacedBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedBinding MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedBinding MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedBinding MimeYaml


-- *** createNamespacedConfigMap

-- | @POST \/api\/v1\/namespaces\/{namespace}\/configmaps@
-- 
-- create a ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedConfigMap
  :: (Consumes CreateNamespacedConfigMap contentType, MimeRender contentType V1ConfigMap)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ConfigMap -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedConfigMap contentType V1ConfigMap accept
createNamespacedConfigMap :: forall contentType accept.
(Consumes CreateNamespacedConfigMap contentType,
 MimeRender contentType V1ConfigMap) =>
ContentType contentType
-> Accept accept
-> V1ConfigMap
-> Namespace
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
createNamespacedConfigMap ContentType contentType
_  Accept accept
_ V1ConfigMap
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps"]
    KubernetesRequest
  CreateNamespacedConfigMap contentType V1ConfigMap accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedConfigMap contentType V1ConfigMap accept
-> V1ConfigMap
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedConfigMap contentType,
 MimeRender contentType V1ConfigMap) =>
KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> V1ConfigMap
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
`setBodyParam` V1ConfigMap
body

data CreateNamespacedConfigMap 
instance HasBodyParam CreateNamespacedConfigMap V1ConfigMap 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedConfigMap DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedConfigMap FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedConfigMap FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedConfigMap mtype

-- | @application/json@
instance Produces CreateNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedConfigMap MimeYaml


-- *** createNamespacedEndpoints

-- | @POST \/api\/v1\/namespaces\/{namespace}\/endpoints@
-- 
-- create Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedEndpoints
  :: (Consumes CreateNamespacedEndpoints contentType, MimeRender contentType V1Endpoints)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Endpoints -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedEndpoints contentType V1Endpoints accept
createNamespacedEndpoints :: forall contentType accept.
(Consumes CreateNamespacedEndpoints contentType,
 MimeRender contentType V1Endpoints) =>
ContentType contentType
-> Accept accept
-> V1Endpoints
-> Namespace
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
createNamespacedEndpoints ContentType contentType
_  Accept accept
_ V1Endpoints
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints"]
    KubernetesRequest
  CreateNamespacedEndpoints contentType V1Endpoints accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedEndpoints contentType V1Endpoints accept
-> V1Endpoints
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedEndpoints contentType,
 MimeRender contentType V1Endpoints) =>
KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> V1Endpoints
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
`setBodyParam` V1Endpoints
body

data CreateNamespacedEndpoints 
instance HasBodyParam CreateNamespacedEndpoints V1Endpoints 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedEndpoints DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedEndpoints FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedEndpoints FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedEndpoints mtype

-- | @application/json@
instance Produces CreateNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedEndpoints MimeYaml


-- *** createNamespacedEvent

-- | @POST \/api\/v1\/namespaces\/{namespace}\/events@
-- 
-- create an Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedEvent
  :: (Consumes CreateNamespacedEvent contentType, MimeRender contentType CoreV1Event)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> CoreV1Event -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedEvent contentType CoreV1Event accept
createNamespacedEvent :: forall contentType accept.
(Consumes CreateNamespacedEvent contentType,
 MimeRender contentType CoreV1Event) =>
ContentType contentType
-> Accept accept
-> CoreV1Event
-> Namespace
-> KubernetesRequest
     CreateNamespacedEvent contentType CoreV1Event accept
createNamespacedEvent ContentType contentType
_  Accept accept
_ CoreV1Event
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedEvent contentType CoreV1Event accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events"]
    KubernetesRequest
  CreateNamespacedEvent contentType CoreV1Event accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedEvent contentType CoreV1Event accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedEvent contentType CoreV1Event accept
-> CoreV1Event
-> KubernetesRequest
     CreateNamespacedEvent contentType CoreV1Event accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedEvent contentType,
 MimeRender contentType CoreV1Event) =>
KubernetesRequest CreateNamespacedEvent contentType res accept
-> CoreV1Event
-> KubernetesRequest CreateNamespacedEvent contentType res accept
`setBodyParam` CoreV1Event
body

data CreateNamespacedEvent 
instance HasBodyParam CreateNamespacedEvent CoreV1Event 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedEvent DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEvent contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedEvent FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEvent contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedEvent FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedEvent contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedEvent mtype

-- | @application/json@
instance Produces CreateNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedEvent MimeYaml


-- *** createNamespacedLimitRange

-- | @POST \/api\/v1\/namespaces\/{namespace}\/limitranges@
-- 
-- create a LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedLimitRange
  :: (Consumes CreateNamespacedLimitRange contentType, MimeRender contentType V1LimitRange)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1LimitRange -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedLimitRange contentType V1LimitRange accept
createNamespacedLimitRange :: forall contentType accept.
(Consumes CreateNamespacedLimitRange contentType,
 MimeRender contentType V1LimitRange) =>
ContentType contentType
-> Accept accept
-> V1LimitRange
-> Namespace
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
createNamespacedLimitRange ContentType contentType
_  Accept accept
_ V1LimitRange
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges"]
    KubernetesRequest
  CreateNamespacedLimitRange contentType V1LimitRange accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedLimitRange contentType V1LimitRange accept
-> V1LimitRange
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedLimitRange contentType,
 MimeRender contentType V1LimitRange) =>
KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> V1LimitRange
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
`setBodyParam` V1LimitRange
body

data CreateNamespacedLimitRange 
instance HasBodyParam CreateNamespacedLimitRange V1LimitRange 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedLimitRange DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedLimitRange FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedLimitRange FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedLimitRange mtype

-- | @application/json@
instance Produces CreateNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedLimitRange MimeYaml


-- *** createNamespacedPersistentVolumeClaim

-- | @POST \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims@
-- 
-- create a PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPersistentVolumeClaim
  :: (Consumes CreateNamespacedPersistentVolumeClaim contentType, MimeRender contentType V1PersistentVolumeClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolumeClaim -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType V1PersistentVolumeClaim accept
createNamespacedPersistentVolumeClaim :: forall contentType accept.
(Consumes CreateNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolumeClaim
-> Namespace
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
createNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ V1PersistentVolumeClaim
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims"]
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
`setBodyParam` V1PersistentVolumeClaim
body

data CreateNamespacedPersistentVolumeClaim 
instance HasBodyParam CreateNamespacedPersistentVolumeClaim V1PersistentVolumeClaim 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPersistentVolumeClaim mtype

-- | @application/json@
instance Produces CreateNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedPersistentVolumeClaim MimeYaml


-- *** createNamespacedPod

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods@
-- 
-- create a Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPod
  :: (Consumes CreateNamespacedPod contentType, MimeRender contentType V1Pod)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Pod -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
createNamespacedPod :: forall contentType accept.
(Consumes CreateNamespacedPod contentType,
 MimeRender contentType V1Pod) =>
ContentType contentType
-> Accept accept
-> V1Pod
-> Namespace
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
createNamespacedPod ContentType contentType
_  Accept accept
_ V1Pod
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods"]
    KubernetesRequest CreateNamespacedPod contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest CreateNamespacedPod contentType V1Pod accept
-> V1Pod
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPod contentType,
 MimeRender contentType V1Pod) =>
KubernetesRequest CreateNamespacedPod contentType res accept
-> V1Pod
-> KubernetesRequest CreateNamespacedPod contentType res accept
`setBodyParam` V1Pod
body

data CreateNamespacedPod 
instance HasBodyParam CreateNamespacedPod V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedPod DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPod contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPod FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPod contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedPod FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPod contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPod mtype

-- | @application/json@
instance Produces CreateNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedPod MimeYaml


-- *** createNamespacedPodBinding

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/binding@
-- 
-- create binding of a Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPodBinding
  :: (Consumes CreateNamespacedPodBinding contentType, MimeRender contentType V1Binding)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Binding -- ^ "body"
  -> Name -- ^ "name" -  name of the Binding
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPodBinding contentType V1Binding accept
createNamespacedPodBinding :: forall contentType accept.
(Consumes CreateNamespacedPodBinding contentType,
 MimeRender contentType V1Binding) =>
ContentType contentType
-> Accept accept
-> V1Binding
-> Name
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
createNamespacedPodBinding ContentType contentType
_  Accept accept
_ V1Binding
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/binding"]
    KubernetesRequest
  CreateNamespacedPodBinding contentType V1Binding accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodBinding contentType V1Binding accept
-> V1Binding
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPodBinding contentType,
 MimeRender contentType V1Binding) =>
KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> V1Binding
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
`setBodyParam` V1Binding
body

data CreateNamespacedPodBinding 
instance HasBodyParam CreateNamespacedPodBinding V1Binding 

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedPodBinding DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPodBinding contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedPodBinding contentType res accept
req KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPodBinding FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPodBinding contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedPodBinding contentType res accept
req KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedPodBinding FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPodBinding contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedPodBinding contentType res accept
req KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedPodBinding Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPodBinding contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedPodBinding contentType res accept
req KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPodBinding mtype

-- | @application/json@
instance Produces CreateNamespacedPodBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodBinding MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedPodBinding MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedPodBinding MimeYaml


-- *** createNamespacedPodEviction

-- | @POST \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/eviction@
-- 
-- create eviction of a Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPodEviction
  :: (Consumes CreateNamespacedPodEviction contentType, MimeRender contentType V1Eviction)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Eviction -- ^ "body"
  -> Name -- ^ "name" -  name of the Eviction
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPodEviction contentType V1Eviction accept
createNamespacedPodEviction :: forall contentType accept.
(Consumes CreateNamespacedPodEviction contentType,
 MimeRender contentType V1Eviction) =>
ContentType contentType
-> Accept accept
-> V1Eviction
-> Name
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1Eviction accept
createNamespacedPodEviction ContentType contentType
_  Accept accept
_ V1Eviction
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1Eviction accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/eviction"]
    KubernetesRequest
  CreateNamespacedPodEviction contentType V1Eviction accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1Eviction accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodEviction contentType V1Eviction accept
-> V1Eviction
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1Eviction accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPodEviction contentType,
 MimeRender contentType V1Eviction) =>
KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> V1Eviction
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
`setBodyParam` V1Eviction
body

data CreateNamespacedPodEviction 
instance HasBodyParam CreateNamespacedPodEviction V1Eviction 

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedPodEviction DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPodEviction FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedPodEviction FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedPodEviction Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPodEviction mtype

-- | @application/json@
instance Produces CreateNamespacedPodEviction MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodEviction MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedPodEviction MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedPodEviction MimeYaml


-- *** createNamespacedPodTemplate

-- | @POST \/api\/v1\/namespaces\/{namespace}\/podtemplates@
-- 
-- create a PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPodTemplate
  :: (Consumes CreateNamespacedPodTemplate contentType, MimeRender contentType V1PodTemplate)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PodTemplate -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPodTemplate contentType V1PodTemplate accept
createNamespacedPodTemplate :: forall contentType accept.
(Consumes CreateNamespacedPodTemplate contentType,
 MimeRender contentType V1PodTemplate) =>
ContentType contentType
-> Accept accept
-> V1PodTemplate
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
createNamespacedPodTemplate ContentType contentType
_  Accept accept
_ V1PodTemplate
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates"]
    KubernetesRequest
  CreateNamespacedPodTemplate contentType V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodTemplate contentType V1PodTemplate accept
-> V1PodTemplate
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPodTemplate contentType,
 MimeRender contentType V1PodTemplate) =>
KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> V1PodTemplate
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
`setBodyParam` V1PodTemplate
body

data CreateNamespacedPodTemplate 
instance HasBodyParam CreateNamespacedPodTemplate V1PodTemplate 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedPodTemplate DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPodTemplate FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedPodTemplate FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPodTemplate mtype

-- | @application/json@
instance Produces CreateNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedPodTemplate MimeYaml


-- *** createNamespacedReplicationController

-- | @POST \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers@
-- 
-- create a ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedReplicationController
  :: (Consumes CreateNamespacedReplicationController contentType, MimeRender contentType V1ReplicationController)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ReplicationController -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedReplicationController contentType V1ReplicationController accept
createNamespacedReplicationController :: forall contentType accept.
(Consumes CreateNamespacedReplicationController contentType,
 MimeRender contentType V1ReplicationController) =>
ContentType contentType
-> Accept accept
-> V1ReplicationController
-> Namespace
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
createNamespacedReplicationController ContentType contentType
_  Accept accept
_ V1ReplicationController
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers"]
    KubernetesRequest
  CreateNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> V1ReplicationController
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedReplicationController contentType,
 MimeRender contentType V1ReplicationController) =>
KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> V1ReplicationController
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
`setBodyParam` V1ReplicationController
body

data CreateNamespacedReplicationController 
instance HasBodyParam CreateNamespacedReplicationController V1ReplicationController 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedReplicationController DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedReplicationController FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedReplicationController FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedReplicationController mtype

-- | @application/json@
instance Produces CreateNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedReplicationController MimeYaml


-- *** createNamespacedResourceQuota

-- | @POST \/api\/v1\/namespaces\/{namespace}\/resourcequotas@
-- 
-- create a ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedResourceQuota
  :: (Consumes CreateNamespacedResourceQuota contentType, MimeRender contentType V1ResourceQuota)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ResourceQuota -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedResourceQuota contentType V1ResourceQuota accept
createNamespacedResourceQuota :: forall contentType accept.
(Consumes CreateNamespacedResourceQuota contentType,
 MimeRender contentType V1ResourceQuota) =>
ContentType contentType
-> Accept accept
-> V1ResourceQuota
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
createNamespacedResourceQuota ContentType contentType
_  Accept accept
_ V1ResourceQuota
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas"]
    KubernetesRequest
  CreateNamespacedResourceQuota contentType V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedResourceQuota contentType V1ResourceQuota accept
-> V1ResourceQuota
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedResourceQuota contentType,
 MimeRender contentType V1ResourceQuota) =>
KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> V1ResourceQuota
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
`setBodyParam` V1ResourceQuota
body

data CreateNamespacedResourceQuota 
instance HasBodyParam CreateNamespacedResourceQuota V1ResourceQuota 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedResourceQuota DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedResourceQuota FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedResourceQuota FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedResourceQuota mtype

-- | @application/json@
instance Produces CreateNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedResourceQuota MimeYaml


-- *** createNamespacedSecret

-- | @POST \/api\/v1\/namespaces\/{namespace}\/secrets@
-- 
-- create a Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedSecret
  :: (Consumes CreateNamespacedSecret contentType, MimeRender contentType V1Secret)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Secret -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedSecret contentType V1Secret accept
createNamespacedSecret :: forall contentType accept.
(Consumes CreateNamespacedSecret contentType,
 MimeRender contentType V1Secret) =>
ContentType contentType
-> Accept accept
-> V1Secret
-> Namespace
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
createNamespacedSecret ContentType contentType
_  Accept accept
_ V1Secret
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets"]
    KubernetesRequest
  CreateNamespacedSecret contentType V1Secret accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedSecret contentType V1Secret accept
-> V1Secret
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedSecret contentType,
 MimeRender contentType V1Secret) =>
KubernetesRequest CreateNamespacedSecret contentType res accept
-> V1Secret
-> KubernetesRequest CreateNamespacedSecret contentType res accept
`setBodyParam` V1Secret
body

data CreateNamespacedSecret 
instance HasBodyParam CreateNamespacedSecret V1Secret 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedSecret contentType res accept
req KubernetesRequest CreateNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedSecret DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedSecret contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedSecret contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedSecret contentType res accept
req KubernetesRequest CreateNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedSecret FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedSecret contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedSecret contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedSecret contentType res accept
req KubernetesRequest CreateNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedSecret FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedSecret contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedSecret contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedSecret contentType res accept
req KubernetesRequest CreateNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedSecret mtype

-- | @application/json@
instance Produces CreateNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedSecret MimeYaml


-- *** createNamespacedService

-- | @POST \/api\/v1\/namespaces\/{namespace}\/services@
-- 
-- create a Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedService
  :: (Consumes CreateNamespacedService contentType, MimeRender contentType V1Service)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Service -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedService contentType V1Service accept
createNamespacedService :: forall contentType accept.
(Consumes CreateNamespacedService contentType,
 MimeRender contentType V1Service) =>
ContentType contentType
-> Accept accept
-> V1Service
-> Namespace
-> KubernetesRequest
     CreateNamespacedService contentType V1Service accept
createNamespacedService ContentType contentType
_  Accept accept
_ V1Service
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedService contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services"]
    KubernetesRequest
  CreateNamespacedService contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedService contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedService contentType V1Service accept
-> V1Service
-> KubernetesRequest
     CreateNamespacedService contentType V1Service accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedService contentType,
 MimeRender contentType V1Service) =>
KubernetesRequest CreateNamespacedService contentType res accept
-> V1Service
-> KubernetesRequest CreateNamespacedService contentType res accept
`setBodyParam` V1Service
body

data CreateNamespacedService 
instance HasBodyParam CreateNamespacedService V1Service 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedService contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedService contentType res accept
req KubernetesRequest CreateNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedService DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedService contentType res accept
-> DryRun
-> KubernetesRequest CreateNamespacedService contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedService contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNamespacedService contentType res accept
req KubernetesRequest CreateNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedService FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedService contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedService contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedService contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedService contentType res accept
req KubernetesRequest CreateNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedService FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNamespacedService contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNamespacedService contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedService contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNamespacedService contentType res accept
req KubernetesRequest CreateNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedService mtype

-- | @application/json@
instance Produces CreateNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedService MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedService MimeYaml


-- *** createNamespacedServiceAccount

-- | @POST \/api\/v1\/namespaces\/{namespace}\/serviceaccounts@
-- 
-- create a ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedServiceAccount
  :: (Consumes CreateNamespacedServiceAccount contentType, MimeRender contentType V1ServiceAccount)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ServiceAccount -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedServiceAccount contentType V1ServiceAccount accept
createNamespacedServiceAccount :: forall contentType accept.
(Consumes CreateNamespacedServiceAccount contentType,
 MimeRender contentType V1ServiceAccount) =>
ContentType contentType
-> Accept accept
-> V1ServiceAccount
-> Namespace
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType V1ServiceAccount accept
createNamespacedServiceAccount ContentType contentType
_  Accept accept
_ V1ServiceAccount
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType V1ServiceAccount accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts"]
    KubernetesRequest
  CreateNamespacedServiceAccount contentType V1ServiceAccount accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType V1ServiceAccount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedServiceAccount contentType V1ServiceAccount accept
-> V1ServiceAccount
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType V1ServiceAccount accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedServiceAccount contentType,
 MimeRender contentType V1ServiceAccount) =>
KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> V1ServiceAccount
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
`setBodyParam` V1ServiceAccount
body

data CreateNamespacedServiceAccount 
instance HasBodyParam CreateNamespacedServiceAccount V1ServiceAccount 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedServiceAccount DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedServiceAccount FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedServiceAccount FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedServiceAccount mtype

-- | @application/json@
instance Produces CreateNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedServiceAccount MimeYaml


-- *** createNamespacedServiceAccountToken

-- | @POST \/api\/v1\/namespaces\/{namespace}\/serviceaccounts\/{name}\/token@
-- 
-- create token of a ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedServiceAccountToken
  :: (Consumes CreateNamespacedServiceAccountToken contentType, MimeRender contentType AuthenticationV1TokenRequest)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> AuthenticationV1TokenRequest -- ^ "body"
  -> Name -- ^ "name" -  name of the TokenRequest
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedServiceAccountToken contentType AuthenticationV1TokenRequest accept
createNamespacedServiceAccountToken :: forall contentType accept.
(Consumes CreateNamespacedServiceAccountToken contentType,
 MimeRender contentType AuthenticationV1TokenRequest) =>
ContentType contentType
-> Accept accept
-> AuthenticationV1TokenRequest
-> Name
-> Namespace
-> KubernetesRequest
     CreateNamespacedServiceAccountToken
     contentType
     AuthenticationV1TokenRequest
     accept
createNamespacedServiceAccountToken ContentType contentType
_  Accept accept
_ AuthenticationV1TokenRequest
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedServiceAccountToken
     contentType
     AuthenticationV1TokenRequest
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/token"]
    KubernetesRequest
  CreateNamespacedServiceAccountToken
  contentType
  AuthenticationV1TokenRequest
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedServiceAccountToken
     contentType
     AuthenticationV1TokenRequest
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedServiceAccountToken
  contentType
  AuthenticationV1TokenRequest
  accept
-> AuthenticationV1TokenRequest
-> KubernetesRequest
     CreateNamespacedServiceAccountToken
     contentType
     AuthenticationV1TokenRequest
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedServiceAccountToken contentType,
 MimeRender contentType AuthenticationV1TokenRequest) =>
KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> AuthenticationV1TokenRequest
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
`setBodyParam` AuthenticationV1TokenRequest
body

data CreateNamespacedServiceAccountToken 
instance HasBodyParam CreateNamespacedServiceAccountToken AuthenticationV1TokenRequest 

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedServiceAccountToken DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedServiceAccountToken FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNamespacedServiceAccountToken FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> FieldValidation
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNamespacedServiceAccountToken Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
req KubernetesRequest
  CreateNamespacedServiceAccountToken contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedServiceAccountToken contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedServiceAccountToken mtype

-- | @application/json@
instance Produces CreateNamespacedServiceAccountToken MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedServiceAccountToken MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNamespacedServiceAccountToken MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedServiceAccountToken MimeYaml


-- *** createNode

-- | @POST \/api\/v1\/nodes@
-- 
-- create a Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNode
  :: (Consumes CreateNode contentType, MimeRender contentType V1Node)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Node -- ^ "body"
  -> KubernetesRequest CreateNode contentType V1Node accept
createNode :: forall contentType accept.
(Consumes CreateNode contentType, MimeRender contentType V1Node) =>
ContentType contentType
-> Accept accept
-> V1Node
-> KubernetesRequest CreateNode contentType V1Node accept
createNode ContentType contentType
_  Accept accept
_ V1Node
body =
  Method
-> [ByteString]
-> KubernetesRequest CreateNode contentType V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/nodes"]
    KubernetesRequest CreateNode contentType V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest CreateNode contentType V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest CreateNode contentType V1Node accept
-> V1Node -> KubernetesRequest CreateNode contentType V1Node accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNode contentType, MimeRender contentType V1Node) =>
KubernetesRequest CreateNode contentType res accept
-> V1Node -> KubernetesRequest CreateNode contentType res accept
`setBodyParam` V1Node
body

data CreateNode 
instance HasBodyParam CreateNode V1Node 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNode contentType res accept
-> Pretty -> KubernetesRequest CreateNode contentType res accept
applyOptionalParam KubernetesRequest CreateNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNode contentType res accept
req KubernetesRequest CreateNode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNode DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNode contentType res accept
-> DryRun -> KubernetesRequest CreateNode contentType res accept
applyOptionalParam KubernetesRequest CreateNode contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateNode contentType res accept
req KubernetesRequest CreateNode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNode FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNode contentType res accept
-> FieldManager
-> KubernetesRequest CreateNode contentType res accept
applyOptionalParam KubernetesRequest CreateNode contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNode contentType res accept
req KubernetesRequest CreateNode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateNode FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateNode contentType res accept
-> FieldValidation
-> KubernetesRequest CreateNode contentType res accept
applyOptionalParam KubernetesRequest CreateNode contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateNode contentType res accept
req KubernetesRequest CreateNode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateNode mtype

-- | @application/json@
instance Produces CreateNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateNode MimeCbor
-- | @application/yaml@
instance Produces CreateNode MimeYaml


-- *** createPersistentVolume

-- | @POST \/api\/v1\/persistentvolumes@
-- 
-- create a PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createPersistentVolume
  :: (Consumes CreatePersistentVolume contentType, MimeRender contentType V1PersistentVolume)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolume -- ^ "body"
  -> KubernetesRequest CreatePersistentVolume contentType V1PersistentVolume accept
createPersistentVolume :: forall contentType accept.
(Consumes CreatePersistentVolume contentType,
 MimeRender contentType V1PersistentVolume) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolume
-> KubernetesRequest
     CreatePersistentVolume contentType V1PersistentVolume accept
createPersistentVolume ContentType contentType
_  Accept accept
_ V1PersistentVolume
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreatePersistentVolume contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/persistentvolumes"]
    KubernetesRequest
  CreatePersistentVolume contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreatePersistentVolume contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreatePersistentVolume contentType V1PersistentVolume accept
-> V1PersistentVolume
-> KubernetesRequest
     CreatePersistentVolume contentType V1PersistentVolume accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreatePersistentVolume contentType,
 MimeRender contentType V1PersistentVolume) =>
KubernetesRequest CreatePersistentVolume contentType res accept
-> V1PersistentVolume
-> KubernetesRequest CreatePersistentVolume contentType res accept
`setBodyParam` V1PersistentVolume
body

data CreatePersistentVolume 
instance HasBodyParam CreatePersistentVolume V1PersistentVolume 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreatePersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreatePersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest CreatePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest CreatePersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreatePersistentVolume contentType res accept
req KubernetesRequest CreatePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest CreatePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreatePersistentVolume DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreatePersistentVolume contentType res accept
-> DryRun
-> KubernetesRequest CreatePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest CreatePersistentVolume contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreatePersistentVolume contentType res accept
req KubernetesRequest CreatePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest CreatePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreatePersistentVolume FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreatePersistentVolume contentType res accept
-> FieldManager
-> KubernetesRequest CreatePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest CreatePersistentVolume contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreatePersistentVolume contentType res accept
req KubernetesRequest CreatePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest CreatePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreatePersistentVolume FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreatePersistentVolume contentType res accept
-> FieldValidation
-> KubernetesRequest CreatePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest CreatePersistentVolume contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreatePersistentVolume contentType res accept
req KubernetesRequest CreatePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest CreatePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreatePersistentVolume mtype

-- | @application/json@
instance Produces CreatePersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreatePersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreatePersistentVolume MimeCbor
-- | @application/yaml@
instance Produces CreatePersistentVolume MimeYaml


-- *** deleteCollectionNamespacedConfigMap

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/configmaps@
-- 
-- delete collection of ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedConfigMap
  :: (Consumes DeleteCollectionNamespacedConfigMap contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType V1Status accept
deleteCollectionNamespacedConfigMap :: forall contentType accept.
Consumes DeleteCollectionNamespacedConfigMap contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType V1Status accept
deleteCollectionNamespacedConfigMap ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps"]
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedConfigMap 
instance HasBodyParam DeleteCollectionNamespacedConfigMap V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedConfigMap DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedConfigMap IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedConfigMap ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedConfigMap ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedConfigMap mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedConfigMap MimeYaml


-- *** deleteCollectionNamespacedEndpoints

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/endpoints@
-- 
-- delete collection of Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedEndpoints
  :: (Consumes DeleteCollectionNamespacedEndpoints contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType V1Status accept
deleteCollectionNamespacedEndpoints :: forall contentType accept.
Consumes DeleteCollectionNamespacedEndpoints contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType V1Status accept
deleteCollectionNamespacedEndpoints ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints"]
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEndpoints 
instance HasBodyParam DeleteCollectionNamespacedEndpoints V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedEndpoints DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedEndpoints IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedEndpoints ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedEndpoints ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedEndpoints mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedEndpoints MimeYaml


-- *** deleteCollectionNamespacedEvent

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/events@
-- 
-- delete collection of Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedEvent
  :: (Consumes DeleteCollectionNamespacedEvent contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEvent contentType V1Status accept
deleteCollectionNamespacedEvent :: forall contentType accept.
Consumes DeleteCollectionNamespacedEvent contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType V1Status accept
deleteCollectionNamespacedEvent ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events"]
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEvent 
instance HasBodyParam DeleteCollectionNamespacedEvent V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedEvent Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedEvent DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedEvent FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedEvent GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedEvent IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedEvent LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedEvent Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedEvent OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedEvent PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedEvent ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedEvent ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedEvent SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedEvent TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedEvent mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedEvent MimeYaml


-- *** deleteCollectionNamespacedLimitRange

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/limitranges@
-- 
-- delete collection of LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedLimitRange
  :: (Consumes DeleteCollectionNamespacedLimitRange contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType V1Status accept
deleteCollectionNamespacedLimitRange :: forall contentType accept.
Consumes DeleteCollectionNamespacedLimitRange contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType V1Status accept
deleteCollectionNamespacedLimitRange ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges"]
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedLimitRange 
instance HasBodyParam DeleteCollectionNamespacedLimitRange V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedLimitRange DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedLimitRange IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedLimitRange ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedLimitRange ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedLimitRange mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedLimitRange MimeYaml


-- *** deleteCollectionNamespacedPersistentVolumeClaim

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims@
-- 
-- delete collection of PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPersistentVolumeClaim
  :: (Consumes DeleteCollectionNamespacedPersistentVolumeClaim contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType V1Status accept
deleteCollectionNamespacedPersistentVolumeClaim :: forall contentType accept.
Consumes
  DeleteCollectionNamespacedPersistentVolumeClaim contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     V1Status
     accept
deleteCollectionNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     V1Status
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims"]
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  V1Status
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     V1Status
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPersistentVolumeClaim 
instance HasBodyParam DeleteCollectionNamespacedPersistentVolumeClaim V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedPersistentVolumeClaim
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPersistentVolumeClaim
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedPersistentVolumeClaim mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeYaml


-- *** deleteCollectionNamespacedPod

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/pods@
-- 
-- delete collection of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPod
  :: (Consumes DeleteCollectionNamespacedPod contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPod contentType V1Status accept
deleteCollectionNamespacedPod :: forall contentType accept.
Consumes DeleteCollectionNamespacedPod contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType V1Status accept
deleteCollectionNamespacedPod ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods"]
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPod 
instance HasBodyParam DeleteCollectionNamespacedPod V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedPod Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedPod DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPod FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedPod GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedPod IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPod LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedPod Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedPod OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedPod PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPod ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPod ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedPod SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedPod TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedPod mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPod MimeYaml


-- *** deleteCollectionNamespacedPodTemplate

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/podtemplates@
-- 
-- delete collection of PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPodTemplate
  :: (Consumes DeleteCollectionNamespacedPodTemplate contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType V1Status accept
deleteCollectionNamespacedPodTemplate :: forall contentType accept.
Consumes DeleteCollectionNamespacedPodTemplate contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType V1Status accept
deleteCollectionNamespacedPodTemplate ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates"]
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPodTemplate 
instance HasBodyParam DeleteCollectionNamespacedPodTemplate V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedPodTemplate mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPodTemplate MimeYaml


-- *** deleteCollectionNamespacedReplicationController

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers@
-- 
-- delete collection of ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedReplicationController
  :: (Consumes DeleteCollectionNamespacedReplicationController contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType V1Status accept
deleteCollectionNamespacedReplicationController :: forall contentType accept.
Consumes
  DeleteCollectionNamespacedReplicationController contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     V1Status
     accept
deleteCollectionNamespacedReplicationController ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     V1Status
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers"]
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  V1Status
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     V1Status
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedReplicationController 
instance HasBodyParam DeleteCollectionNamespacedReplicationController V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedReplicationController DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedReplicationController IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedReplicationController ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedReplicationController ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
req KubernetesRequest
  DeleteCollectionNamespacedReplicationController
  contentType
  res
  accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedReplicationController
     contentType
     res
     accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedReplicationController mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedReplicationController MimeYaml


-- *** deleteCollectionNamespacedResourceQuota

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/resourcequotas@
-- 
-- delete collection of ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedResourceQuota
  :: (Consumes DeleteCollectionNamespacedResourceQuota contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType V1Status accept
deleteCollectionNamespacedResourceQuota :: forall contentType accept.
Consumes DeleteCollectionNamespacedResourceQuota contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType V1Status accept
deleteCollectionNamespacedResourceQuota ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas"]
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedResourceQuota 
instance HasBodyParam DeleteCollectionNamespacedResourceQuota V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedResourceQuota mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedResourceQuota MimeYaml


-- *** deleteCollectionNamespacedSecret

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/secrets@
-- 
-- delete collection of Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedSecret
  :: (Consumes DeleteCollectionNamespacedSecret contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedSecret contentType V1Status accept
deleteCollectionNamespacedSecret :: forall contentType accept.
Consumes DeleteCollectionNamespacedSecret contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType V1Status accept
deleteCollectionNamespacedSecret ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets"]
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedSecret 
instance HasBodyParam DeleteCollectionNamespacedSecret V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedSecret Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedSecret DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedSecret FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedSecret GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedSecret IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedSecret LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedSecret Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedSecret OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedSecret PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedSecret ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedSecret ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedSecret SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedSecret TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedSecret mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedSecret MimeYaml


-- *** deleteCollectionNamespacedService

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/services@
-- 
-- delete collection of Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedService
  :: (Consumes DeleteCollectionNamespacedService contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedService contentType V1Status accept
deleteCollectionNamespacedService :: forall contentType accept.
Consumes DeleteCollectionNamespacedService contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType V1Status accept
deleteCollectionNamespacedService ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services"]
    KubernetesRequest
  DeleteCollectionNamespacedService contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedService 
instance HasBodyParam DeleteCollectionNamespacedService V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedService Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedService DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedService FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedService GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedService IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedService LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedService Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedService OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedService PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedService ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedService ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedService SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedService TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedService mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedService MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedService MimeYaml


-- *** deleteCollectionNamespacedServiceAccount

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/serviceaccounts@
-- 
-- delete collection of ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedServiceAccount
  :: (Consumes DeleteCollectionNamespacedServiceAccount contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType V1Status accept
deleteCollectionNamespacedServiceAccount :: forall contentType accept.
Consumes DeleteCollectionNamespacedServiceAccount contentType =>
ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount
     contentType
     V1Status
     accept
deleteCollectionNamespacedServiceAccount ContentType contentType
_  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount
     contentType
     V1Status
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts"]
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount
  contentType
  V1Status
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount
     contentType
     V1Status
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedServiceAccount 
instance HasBodyParam DeleteCollectionNamespacedServiceAccount V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteCollectionNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNamespacedServiceAccount mtype

-- | @application/json@
instance Produces DeleteCollectionNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedServiceAccount MimeYaml


-- *** deleteCollectionNode

-- | @DELETE \/api\/v1\/nodes@
-- 
-- delete collection of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNode
  :: (Consumes DeleteCollectionNode contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionNode contentType V1Status accept
deleteCollectionNode :: forall contentType accept.
Consumes DeleteCollectionNode contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionNode contentType V1Status accept
deleteCollectionNode ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionNode contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/nodes"]
    KubernetesRequest DeleteCollectionNode contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionNode contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNode 
instance HasBodyParam DeleteCollectionNode V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> Pretty
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionNode Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> Continue
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (Continue Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNode DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> DryRun
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionNode FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> FieldSelector
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNode GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionNode IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionNode LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> LabelSelector
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionNode Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> Limit
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (Limit Int
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNode OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionNode PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNode ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> ResourceVersion
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionNode ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionNode SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> SendInitialEvents
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionNode TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionNode contentType res accept
-> TimeoutSeconds
-> KubernetesRequest DeleteCollectionNode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionNode contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest DeleteCollectionNode contentType res accept
req KubernetesRequest DeleteCollectionNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionNode mtype

-- | @application/json@
instance Produces DeleteCollectionNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionNode MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNode MimeYaml


-- *** deleteCollectionPersistentVolume

-- | @DELETE \/api\/v1\/persistentvolumes@
-- 
-- delete collection of PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionPersistentVolume
  :: (Consumes DeleteCollectionPersistentVolume contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionPersistentVolume contentType V1Status accept
deleteCollectionPersistentVolume :: forall contentType accept.
Consumes DeleteCollectionPersistentVolume contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType V1Status accept
deleteCollectionPersistentVolume ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/persistentvolumes"]
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionPersistentVolume 
instance HasBodyParam DeleteCollectionPersistentVolume V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionPersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionPersistentVolume Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionPersistentVolume DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionPersistentVolume FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionPersistentVolume GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionPersistentVolume IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionPersistentVolume LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionPersistentVolume Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionPersistentVolume OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionPersistentVolume PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionPersistentVolume ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionPersistentVolume ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionPersistentVolume SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionPersistentVolume TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
req KubernetesRequest
  DeleteCollectionPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionPersistentVolume mtype

-- | @application/json@
instance Produces DeleteCollectionPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionPersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionPersistentVolume MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionPersistentVolume MimeYaml


-- *** deleteNamespace

-- | @DELETE \/api\/v1\/namespaces\/{name}@
-- 
-- delete a Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespace
  :: (Consumes DeleteNamespace contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest DeleteNamespace contentType V1Status accept
deleteNamespace :: forall contentType accept.
Consumes DeleteNamespace contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteNamespace contentType V1Status accept
deleteNamespace ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteNamespace contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteNamespace contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteNamespace contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespace 
instance HasBodyParam DeleteNamespace V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> Pretty
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespace DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> DryRun
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespace GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespace IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespace OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespace PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespace contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNamespace contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespace contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespace contentType res accept
req KubernetesRequest DeleteNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespace mtype

-- | @application/json@
instance Produces DeleteNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespace MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespace MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespace MimeYaml


-- *** deleteNamespacedConfigMap

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/configmaps\/{name}@
-- 
-- delete a ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedConfigMap
  :: (Consumes DeleteNamespacedConfigMap contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ConfigMap
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedConfigMap contentType V1Status accept
deleteNamespacedConfigMap :: forall contentType accept.
Consumes DeleteNamespacedConfigMap contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType V1Status accept
deleteNamespacedConfigMap ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedConfigMap contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedConfigMap 
instance HasBodyParam DeleteNamespacedConfigMap V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedConfigMap DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedConfigMap GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedConfigMap IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedConfigMap OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedConfigMap PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedConfigMap contentType res accept
req KubernetesRequest DeleteNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedConfigMap mtype

-- | @application/json@
instance Produces DeleteNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedConfigMap MimeYaml


-- *** deleteNamespacedEndpoints

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/endpoints\/{name}@
-- 
-- delete Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedEndpoints
  :: (Consumes DeleteNamespacedEndpoints contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Endpoints
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedEndpoints contentType V1Status accept
deleteNamespacedEndpoints :: forall contentType accept.
Consumes DeleteNamespacedEndpoints contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType V1Status accept
deleteNamespacedEndpoints ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedEndpoints contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedEndpoints 
instance HasBodyParam DeleteNamespacedEndpoints V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedEndpoints DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedEndpoints GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedEndpoints IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedEndpoints OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedEndpoints PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedEndpoints contentType res accept
req KubernetesRequest DeleteNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedEndpoints mtype

-- | @application/json@
instance Produces DeleteNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedEndpoints MimeYaml


-- *** deleteNamespacedEvent

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/events\/{name}@
-- 
-- delete an Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedEvent
  :: (Consumes DeleteNamespacedEvent contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Event
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedEvent contentType V1Status accept
deleteNamespacedEvent :: forall contentType accept.
Consumes DeleteNamespacedEvent contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedEvent contentType V1Status accept
deleteNamespacedEvent ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedEvent contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteNamespacedEvent contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedEvent contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedEvent 
instance HasBodyParam DeleteNamespacedEvent V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedEvent DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> DryRun
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedEvent GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedEvent IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedEvent OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedEvent PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedEvent contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedEvent contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedEvent contentType res accept
req KubernetesRequest DeleteNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedEvent mtype

-- | @application/json@
instance Produces DeleteNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedEvent MimeYaml


-- *** deleteNamespacedLimitRange

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/limitranges\/{name}@
-- 
-- delete a LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedLimitRange
  :: (Consumes DeleteNamespacedLimitRange contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the LimitRange
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedLimitRange contentType V1Status accept
deleteNamespacedLimitRange :: forall contentType accept.
Consumes DeleteNamespacedLimitRange contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType V1Status accept
deleteNamespacedLimitRange ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedLimitRange contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedLimitRange 
instance HasBodyParam DeleteNamespacedLimitRange V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedLimitRange DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedLimitRange GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedLimitRange IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedLimitRange OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedLimitRange PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedLimitRange contentType res accept
req KubernetesRequest DeleteNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedLimitRange mtype

-- | @application/json@
instance Produces DeleteNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedLimitRange MimeYaml


-- *** deleteNamespacedPersistentVolumeClaim

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}@
-- 
-- delete a PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedPersistentVolumeClaim
  :: (Consumes DeleteNamespacedPersistentVolumeClaim contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType V1PersistentVolumeClaim accept
deleteNamespacedPersistentVolumeClaim :: forall contentType accept.
Consumes DeleteNamespacedPersistentVolumeClaim contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
deleteNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPersistentVolumeClaim 
instance HasBodyParam DeleteNamespacedPersistentVolumeClaim V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  DeleteNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedPersistentVolumeClaim mtype

-- | @application/json@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeYaml


-- *** deleteNamespacedPod

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/pods\/{name}@
-- 
-- delete a Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedPod
  :: (Consumes DeleteNamespacedPod contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedPod contentType V1Pod accept
deleteNamespacedPod :: forall contentType accept.
Consumes DeleteNamespacedPod contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedPod contentType V1Pod accept
deleteNamespacedPod ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteNamespacedPod contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteNamespacedPod contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteNamespacedPod contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPod 
instance HasBodyParam DeleteNamespacedPod V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedPod DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> DryRun
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedPod GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedPod IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedPod OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedPod PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedPod contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedPod contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedPod contentType res accept
req KubernetesRequest DeleteNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedPod mtype

-- | @application/json@
instance Produces DeleteNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedPod MimeYaml


-- *** deleteNamespacedPodTemplate

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/podtemplates\/{name}@
-- 
-- delete a PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedPodTemplate
  :: (Consumes DeleteNamespacedPodTemplate contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedPodTemplate contentType V1PodTemplate accept
deleteNamespacedPodTemplate :: forall contentType accept.
Consumes DeleteNamespacedPodTemplate contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType V1PodTemplate accept
deleteNamespacedPodTemplate ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPodTemplate 
instance HasBodyParam DeleteNamespacedPodTemplate V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedPodTemplate DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedPodTemplate GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedPodTemplate IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedPodTemplate OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedPodTemplate PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
req KubernetesRequest
  DeleteNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedPodTemplate mtype

-- | @application/json@
instance Produces DeleteNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedPodTemplate MimeYaml


-- *** deleteNamespacedReplicationController

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}@
-- 
-- delete a ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedReplicationController
  :: (Consumes DeleteNamespacedReplicationController contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedReplicationController contentType V1Status accept
deleteNamespacedReplicationController :: forall contentType accept.
Consumes DeleteNamespacedReplicationController contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType V1Status accept
deleteNamespacedReplicationController ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedReplicationController contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedReplicationController 
instance HasBodyParam DeleteNamespacedReplicationController V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedReplicationController DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedReplicationController GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedReplicationController IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedReplicationController OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedReplicationController PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
req KubernetesRequest
  DeleteNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedReplicationController mtype

-- | @application/json@
instance Produces DeleteNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedReplicationController MimeYaml


-- *** deleteNamespacedResourceQuota

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}@
-- 
-- delete a ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedResourceQuota
  :: (Consumes DeleteNamespacedResourceQuota contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedResourceQuota contentType V1ResourceQuota accept
deleteNamespacedResourceQuota :: forall contentType accept.
Consumes DeleteNamespacedResourceQuota contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType V1ResourceQuota accept
deleteNamespacedResourceQuota ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedResourceQuota 
instance HasBodyParam DeleteNamespacedResourceQuota V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedResourceQuota DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedResourceQuota GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedResourceQuota IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedResourceQuota OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedResourceQuota PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
req KubernetesRequest
  DeleteNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedResourceQuota mtype

-- | @application/json@
instance Produces DeleteNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedResourceQuota MimeYaml


-- *** deleteNamespacedSecret

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/secrets\/{name}@
-- 
-- delete a Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedSecret
  :: (Consumes DeleteNamespacedSecret contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Secret
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedSecret contentType V1Status accept
deleteNamespacedSecret :: forall contentType accept.
Consumes DeleteNamespacedSecret contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedSecret contentType V1Status accept
deleteNamespacedSecret ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedSecret contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedSecret contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedSecret contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedSecret 
instance HasBodyParam DeleteNamespacedSecret V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedSecret DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> DryRun
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedSecret GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedSecret IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedSecret OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedSecret PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedSecret contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedSecret contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedSecret contentType res accept
req KubernetesRequest DeleteNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedSecret mtype

-- | @application/json@
instance Produces DeleteNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedSecret MimeYaml


-- *** deleteNamespacedService

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/services\/{name}@
-- 
-- delete a Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedService
  :: (Consumes DeleteNamespacedService contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedService contentType V1Service accept
deleteNamespacedService :: forall contentType accept.
Consumes DeleteNamespacedService contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedService contentType V1Service accept
deleteNamespacedService ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedService contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedService contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedService contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedService 
instance HasBodyParam DeleteNamespacedService V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedService DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> DryRun
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedService GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedService IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedService OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedService PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNamespacedService contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNamespacedService contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedService contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNamespacedService contentType res accept
req KubernetesRequest DeleteNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedService mtype

-- | @application/json@
instance Produces DeleteNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedService MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedService MimeYaml


-- *** deleteNamespacedServiceAccount

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/serviceaccounts\/{name}@
-- 
-- delete a ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedServiceAccount
  :: (Consumes DeleteNamespacedServiceAccount contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceAccount
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedServiceAccount contentType V1ServiceAccount accept
deleteNamespacedServiceAccount :: forall contentType accept.
Consumes DeleteNamespacedServiceAccount contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType V1ServiceAccount accept
deleteNamespacedServiceAccount ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType V1ServiceAccount accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType V1ServiceAccount accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType V1ServiceAccount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedServiceAccount 
instance HasBodyParam DeleteNamespacedServiceAccount V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNamespacedServiceAccount DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNamespacedServiceAccount GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedServiceAccount IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNamespacedServiceAccount OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNamespacedServiceAccount PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
req KubernetesRequest
  DeleteNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNamespacedServiceAccount mtype

-- | @application/json@
instance Produces DeleteNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedServiceAccount MimeYaml


-- *** deleteNode

-- | @DELETE \/api\/v1\/nodes\/{name}@
-- 
-- delete a Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNode
  :: (Consumes DeleteNode contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest DeleteNode contentType V1Status accept
deleteNode :: forall contentType accept.
Consumes DeleteNode contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteNode contentType V1Status accept
deleteNode ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteNode contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteNode contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteNode contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNode 
instance HasBodyParam DeleteNode V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> Pretty -> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteNode DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> DryRun -> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteNode GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNode IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteNode OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteNode PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteNode contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteNode contentType res accept
applyOptionalParam KubernetesRequest DeleteNode contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteNode contentType res accept
req KubernetesRequest DeleteNode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteNode mtype

-- | @application/json@
instance Produces DeleteNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteNode MimeCbor
-- | @application/yaml@
instance Produces DeleteNode MimeYaml


-- *** deletePersistentVolume

-- | @DELETE \/api\/v1\/persistentvolumes\/{name}@
-- 
-- delete a PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deletePersistentVolume
  :: (Consumes DeletePersistentVolume contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest DeletePersistentVolume contentType V1PersistentVolume accept
deletePersistentVolume :: forall contentType accept.
Consumes DeletePersistentVolume contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeletePersistentVolume contentType V1PersistentVolume accept
deletePersistentVolume ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeletePersistentVolume contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeletePersistentVolume contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeletePersistentVolume contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeletePersistentVolume 
instance HasBodyParam DeletePersistentVolume V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeletePersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeletePersistentVolume DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> DryRun
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeletePersistentVolume GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeletePersistentVolume IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeletePersistentVolume OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> OrphanDependents
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeletePersistentVolume PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeletePersistentVolume contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeletePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest DeletePersistentVolume contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeletePersistentVolume contentType res accept
req KubernetesRequest DeletePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest DeletePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeletePersistentVolume mtype

-- | @application/json@
instance Produces DeletePersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeletePersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeletePersistentVolume MimeCbor
-- | @application/yaml@
instance Produces DeletePersistentVolume MimeYaml


-- *** getAPIResources

-- | @GET \/api\/v1\/@
-- 
-- get available resources
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
getAPIResources
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources :: forall accept.
Accept accept
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/"]
    KubernetesRequest
  GetAPIResources MimeNoContent V1APIResourceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data GetAPIResources  
-- | @application/json@
instance Produces GetAPIResources MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces GetAPIResources MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces GetAPIResources MimeCbor
-- | @application/yaml@
instance Produces GetAPIResources MimeYaml


-- *** listComponentStatus

-- | @GET \/api\/v1\/componentstatuses@
-- 
-- list objects of kind ComponentStatus
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listComponentStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListComponentStatus MimeNoContent V1ComponentStatusList accept
listComponentStatus :: forall accept.
Accept accept
-> KubernetesRequest
     ListComponentStatus MimeNoContent V1ComponentStatusList accept
listComponentStatus  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListComponentStatus MimeNoContent V1ComponentStatusList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/componentstatuses"]
    KubernetesRequest
  ListComponentStatus MimeNoContent V1ComponentStatusList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListComponentStatus MimeNoContent V1ComponentStatusList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListComponentStatus  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListComponentStatus AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListComponentStatus Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> Continue
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListComponentStatus FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> FieldSelector
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListComponentStatus LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> LabelSelector
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListComponentStatus Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> Limit
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListComponentStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> Pretty
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListComponentStatus ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> ResourceVersion
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListComponentStatus ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListComponentStatus SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListComponentStatus TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListComponentStatus Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListComponentStatus contentType res accept
-> Watch
-> KubernetesRequest ListComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ListComponentStatus contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListComponentStatus contentType res accept
req KubernetesRequest ListComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ListComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListComponentStatus MimeCborSeq
-- | @application/json@
instance Produces ListComponentStatus MimeJSON
-- | @application/json;stream=watch@
instance Produces ListComponentStatus MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListComponentStatus MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListComponentStatus MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListComponentStatus MimeCbor
-- | @application/yaml@
instance Produces ListComponentStatus MimeYaml


-- *** listConfigMapForAllNamespaces

-- | @GET \/api\/v1\/configmaps@
-- 
-- list or watch objects of kind ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listConfigMapForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListConfigMapForAllNamespaces MimeNoContent V1ConfigMapList accept
listConfigMapForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListConfigMapForAllNamespaces MimeNoContent V1ConfigMapList accept
listConfigMapForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListConfigMapForAllNamespaces MimeNoContent V1ConfigMapList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/configmaps"]
    KubernetesRequest
  ListConfigMapForAllNamespaces MimeNoContent V1ConfigMapList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListConfigMapForAllNamespaces MimeNoContent V1ConfigMapList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListConfigMapForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListConfigMapForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListConfigMapForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListConfigMapForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListConfigMapForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListConfigMapForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListConfigMapForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListConfigMapForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListConfigMapForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListConfigMapForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListConfigMapForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListConfigMapForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
req KubernetesRequest
  ListConfigMapForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListConfigMapForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListConfigMapForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListConfigMapForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListConfigMapForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListConfigMapForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListConfigMapForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListConfigMapForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListConfigMapForAllNamespaces MimeYaml


-- *** listEndpointsForAllNamespaces

-- | @GET \/api\/v1\/endpoints@
-- 
-- list or watch objects of kind Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listEndpointsForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListEndpointsForAllNamespaces MimeNoContent V1EndpointsList accept
listEndpointsForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListEndpointsForAllNamespaces MimeNoContent V1EndpointsList accept
listEndpointsForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListEndpointsForAllNamespaces MimeNoContent V1EndpointsList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/endpoints"]
    KubernetesRequest
  ListEndpointsForAllNamespaces MimeNoContent V1EndpointsList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListEndpointsForAllNamespaces MimeNoContent V1EndpointsList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListEndpointsForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListEndpointsForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListEndpointsForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListEndpointsForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListEndpointsForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListEndpointsForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListEndpointsForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListEndpointsForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListEndpointsForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListEndpointsForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListEndpointsForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListEndpointsForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
req KubernetesRequest
  ListEndpointsForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEndpointsForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListEndpointsForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListEndpointsForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListEndpointsForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListEndpointsForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListEndpointsForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListEndpointsForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListEndpointsForAllNamespaces MimeYaml


-- *** listEventForAllNamespaces

-- | @GET \/api\/v1\/events@
-- 
-- list or watch objects of kind Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listEventForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListEventForAllNamespaces MimeNoContent CoreV1EventList accept
listEventForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListEventForAllNamespaces MimeNoContent CoreV1EventList accept
listEventForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListEventForAllNamespaces MimeNoContent CoreV1EventList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/events"]
    KubernetesRequest
  ListEventForAllNamespaces MimeNoContent CoreV1EventList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListEventForAllNamespaces MimeNoContent CoreV1EventList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListEventForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListEventForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListEventForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListEventForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListEventForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListEventForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListEventForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListEventForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListEventForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListEventForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListEventForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListEventForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListEventForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListEventForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListEventForAllNamespaces contentType res accept
req KubernetesRequest ListEventForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListEventForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListEventForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListEventForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListEventForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListEventForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListEventForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListEventForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListEventForAllNamespaces MimeYaml


-- *** listLimitRangeForAllNamespaces

-- | @GET \/api\/v1\/limitranges@
-- 
-- list or watch objects of kind LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listLimitRangeForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListLimitRangeForAllNamespaces MimeNoContent V1LimitRangeList accept
listLimitRangeForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListLimitRangeForAllNamespaces
     MimeNoContent
     V1LimitRangeList
     accept
listLimitRangeForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces
     MimeNoContent
     V1LimitRangeList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/limitranges"]
    KubernetesRequest
  ListLimitRangeForAllNamespaces
  MimeNoContent
  V1LimitRangeList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListLimitRangeForAllNamespaces
     MimeNoContent
     V1LimitRangeList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListLimitRangeForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListLimitRangeForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListLimitRangeForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListLimitRangeForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListLimitRangeForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListLimitRangeForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListLimitRangeForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListLimitRangeForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListLimitRangeForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListLimitRangeForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListLimitRangeForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListLimitRangeForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
req KubernetesRequest
  ListLimitRangeForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListLimitRangeForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListLimitRangeForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListLimitRangeForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListLimitRangeForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListLimitRangeForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListLimitRangeForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListLimitRangeForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListLimitRangeForAllNamespaces MimeYaml


-- *** listNamespace

-- | @GET \/api\/v1\/namespaces@
-- 
-- list or watch objects of kind Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespace
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListNamespace MimeNoContent V1NamespaceList accept
listNamespace :: forall accept.
Accept accept
-> KubernetesRequest
     ListNamespace MimeNoContent V1NamespaceList accept
listNamespace  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespace MimeNoContent V1NamespaceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces"]
    KubernetesRequest
  ListNamespace MimeNoContent V1NamespaceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespace MimeNoContent V1NamespaceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespace  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> Pretty -> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespace AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespace Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> Continue
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespace FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespace LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespace Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> Limit -> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespace ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespace ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespace SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespace TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespace Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespace contentType res accept
-> Watch -> KubernetesRequest ListNamespace contentType res accept
applyOptionalParam KubernetesRequest ListNamespace contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespace contentType res accept
req KubernetesRequest ListNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespace MimeCborSeq
-- | @application/json@
instance Produces ListNamespace MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespace MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespace MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespace MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespace MimeCbor
-- | @application/yaml@
instance Produces ListNamespace MimeYaml


-- *** listNamespacedConfigMap

-- | @GET \/api\/v1\/namespaces\/{namespace}\/configmaps@
-- 
-- list or watch objects of kind ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedConfigMap
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedConfigMap MimeNoContent V1ConfigMapList accept
listNamespacedConfigMap :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedConfigMap MimeNoContent V1ConfigMapList accept
listNamespacedConfigMap  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedConfigMap MimeNoContent V1ConfigMapList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps"]
    KubernetesRequest
  ListNamespacedConfigMap MimeNoContent V1ConfigMapList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedConfigMap MimeNoContent V1ConfigMapList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedConfigMap  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedConfigMap AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedConfigMap Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedConfigMap FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedConfigMap LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedConfigMap Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedConfigMap ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedConfigMap ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedConfigMap SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedConfigMap TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedConfigMap Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedConfigMap contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedConfigMap contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedConfigMap contentType res accept
req KubernetesRequest ListNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedConfigMap MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedConfigMap MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedConfigMap MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedConfigMap MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedConfigMap MimeYaml


-- *** listNamespacedEndpoints

-- | @GET \/api\/v1\/namespaces\/{namespace}\/endpoints@
-- 
-- list or watch objects of kind Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedEndpoints
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedEndpoints MimeNoContent V1EndpointsList accept
listNamespacedEndpoints :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedEndpoints MimeNoContent V1EndpointsList accept
listNamespacedEndpoints  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedEndpoints MimeNoContent V1EndpointsList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints"]
    KubernetesRequest
  ListNamespacedEndpoints MimeNoContent V1EndpointsList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedEndpoints MimeNoContent V1EndpointsList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedEndpoints  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedEndpoints AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedEndpoints Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedEndpoints FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedEndpoints LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedEndpoints Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedEndpoints ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedEndpoints ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedEndpoints SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedEndpoints TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedEndpoints Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEndpoints contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEndpoints contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedEndpoints contentType res accept
req KubernetesRequest ListNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedEndpoints MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedEndpoints MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedEndpoints MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedEndpoints MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedEndpoints MimeYaml


-- *** listNamespacedEvent

-- | @GET \/api\/v1\/namespaces\/{namespace}\/events@
-- 
-- list or watch objects of kind Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedEvent
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedEvent MimeNoContent CoreV1EventList accept
listNamespacedEvent :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedEvent MimeNoContent CoreV1EventList accept
listNamespacedEvent  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedEvent MimeNoContent CoreV1EventList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events"]
    KubernetesRequest
  ListNamespacedEvent MimeNoContent CoreV1EventList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedEvent MimeNoContent CoreV1EventList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedEvent  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedEvent AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedEvent Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedEvent FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedEvent LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedEvent Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedEvent ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedEvent ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedEvent SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedEvent TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedEvent Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedEvent contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedEvent contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedEvent contentType res accept
req KubernetesRequest ListNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedEvent MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedEvent MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedEvent MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedEvent MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedEvent MimeYaml


-- *** listNamespacedLimitRange

-- | @GET \/api\/v1\/namespaces\/{namespace}\/limitranges@
-- 
-- list or watch objects of kind LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedLimitRange
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedLimitRange MimeNoContent V1LimitRangeList accept
listNamespacedLimitRange :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedLimitRange MimeNoContent V1LimitRangeList accept
listNamespacedLimitRange  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedLimitRange MimeNoContent V1LimitRangeList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges"]
    KubernetesRequest
  ListNamespacedLimitRange MimeNoContent V1LimitRangeList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedLimitRange MimeNoContent V1LimitRangeList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedLimitRange  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedLimitRange AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedLimitRange Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedLimitRange FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedLimitRange LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedLimitRange Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedLimitRange ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedLimitRange ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedLimitRange SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedLimitRange TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedLimitRange Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedLimitRange contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedLimitRange contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedLimitRange contentType res accept
req KubernetesRequest ListNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedLimitRange MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedLimitRange MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedLimitRange MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedLimitRange MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedLimitRange MimeYaml


-- *** listNamespacedPersistentVolumeClaim

-- | @GET \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims@
-- 
-- list or watch objects of kind PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedPersistentVolumeClaim
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedPersistentVolumeClaim MimeNoContent V1PersistentVolumeClaimList accept
listNamespacedPersistentVolumeClaim :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
listNamespacedPersistentVolumeClaim  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims"]
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim
  MimeNoContent
  V1PersistentVolumeClaimList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPersistentVolumeClaim  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPersistentVolumeClaim ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPersistentVolumeClaim ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ListNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedPersistentVolumeClaim MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedPersistentVolumeClaim MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedPersistentVolumeClaim MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedPersistentVolumeClaim MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedPersistentVolumeClaim MimeYaml


-- *** listNamespacedPod

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods@
-- 
-- list or watch objects of kind Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedPod
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedPod MimeNoContent V1PodList accept
listNamespacedPod :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedPod MimeNoContent V1PodList accept
listNamespacedPod  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedPod MimeNoContent V1PodList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods"]
    KubernetesRequest ListNamespacedPod MimeNoContent V1PodList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedPod MimeNoContent V1PodList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPod  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedPod AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedPod Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedPod FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedPod LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedPod Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPod ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPod ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedPod SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedPod TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedPod Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPod contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPod contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedPod contentType res accept
req KubernetesRequest ListNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedPod MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedPod MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedPod MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedPod MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedPod MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedPod MimeYaml


-- *** listNamespacedPodTemplate

-- | @GET \/api\/v1\/namespaces\/{namespace}\/podtemplates@
-- 
-- list or watch objects of kind PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedPodTemplate
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedPodTemplate MimeNoContent V1PodTemplateList accept
listNamespacedPodTemplate :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedPodTemplate MimeNoContent V1PodTemplateList accept
listNamespacedPodTemplate  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedPodTemplate MimeNoContent V1PodTemplateList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates"]
    KubernetesRequest
  ListNamespacedPodTemplate MimeNoContent V1PodTemplateList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedPodTemplate MimeNoContent V1PodTemplateList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPodTemplate  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedPodTemplate AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedPodTemplate Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedPodTemplate FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedPodTemplate LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedPodTemplate Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPodTemplate ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedPodTemplate ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedPodTemplate SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedPodTemplate TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedPodTemplate Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedPodTemplate contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedPodTemplate contentType res accept
req KubernetesRequest ListNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedPodTemplate MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedPodTemplate MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedPodTemplate MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedPodTemplate MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedPodTemplate MimeYaml


-- *** listNamespacedReplicationController

-- | @GET \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers@
-- 
-- list or watch objects of kind ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedReplicationController
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedReplicationController MimeNoContent V1ReplicationControllerList accept
listNamespacedReplicationController :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedReplicationController
     MimeNoContent
     V1ReplicationControllerList
     accept
listNamespacedReplicationController  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedReplicationController
     MimeNoContent
     V1ReplicationControllerList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers"]
    KubernetesRequest
  ListNamespacedReplicationController
  MimeNoContent
  V1ReplicationControllerList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedReplicationController
     MimeNoContent
     V1ReplicationControllerList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedReplicationController  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedReplicationController AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedReplicationController Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedReplicationController FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedReplicationController LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedReplicationController Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedReplicationController ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedReplicationController ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedReplicationController SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedReplicationController TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedReplicationController Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListNamespacedReplicationController contentType res accept
req KubernetesRequest
  ListNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedReplicationController MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedReplicationController MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedReplicationController MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedReplicationController MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedReplicationController MimeYaml


-- *** listNamespacedResourceQuota

-- | @GET \/api\/v1\/namespaces\/{namespace}\/resourcequotas@
-- 
-- list or watch objects of kind ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedResourceQuota
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedResourceQuota MimeNoContent V1ResourceQuotaList accept
listNamespacedResourceQuota :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceQuota
     MimeNoContent
     V1ResourceQuotaList
     accept
listNamespacedResourceQuota  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceQuota
     MimeNoContent
     V1ResourceQuotaList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas"]
    KubernetesRequest
  ListNamespacedResourceQuota
  MimeNoContent
  V1ResourceQuotaList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceQuota
     MimeNoContent
     V1ResourceQuotaList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedResourceQuota  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedResourceQuota AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedResourceQuota Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedResourceQuota FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedResourceQuota LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedResourceQuota Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedResourceQuota ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedResourceQuota ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedResourceQuota SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedResourceQuota TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedResourceQuota Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ListNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedResourceQuota MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedResourceQuota MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedResourceQuota MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedResourceQuota MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedResourceQuota MimeYaml


-- *** listNamespacedSecret

-- | @GET \/api\/v1\/namespaces\/{namespace}\/secrets@
-- 
-- list or watch objects of kind Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedSecret
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedSecret MimeNoContent V1SecretList accept
listNamespacedSecret :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedSecret MimeNoContent V1SecretList accept
listNamespacedSecret  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedSecret MimeNoContent V1SecretList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets"]
    KubernetesRequest
  ListNamespacedSecret MimeNoContent V1SecretList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedSecret MimeNoContent V1SecretList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedSecret  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedSecret AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedSecret Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedSecret FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedSecret LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedSecret Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedSecret ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedSecret ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedSecret SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedSecret TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedSecret Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedSecret contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedSecret contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedSecret contentType res accept
req KubernetesRequest ListNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedSecret MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedSecret MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedSecret MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedSecret MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedSecret MimeYaml


-- *** listNamespacedService

-- | @GET \/api\/v1\/namespaces\/{namespace}\/services@
-- 
-- list or watch objects of kind Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedService
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedService MimeNoContent V1ServiceList accept
listNamespacedService :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedService MimeNoContent V1ServiceList accept
listNamespacedService  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedService MimeNoContent V1ServiceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services"]
    KubernetesRequest
  ListNamespacedService MimeNoContent V1ServiceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedService MimeNoContent V1ServiceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedService  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedService AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedService Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedService FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedService LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedService Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedService ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedService ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedService SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedService TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedService Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNamespacedService contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedService contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNamespacedService contentType res accept
req KubernetesRequest ListNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedService MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedService MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedService MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedService MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedService MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedService MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedService MimeYaml


-- *** listNamespacedServiceAccount

-- | @GET \/api\/v1\/namespaces\/{namespace}\/serviceaccounts@
-- 
-- list or watch objects of kind ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedServiceAccount
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedServiceAccount MimeNoContent V1ServiceAccountList accept
listNamespacedServiceAccount :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedServiceAccount
     MimeNoContent
     V1ServiceAccountList
     accept
listNamespacedServiceAccount  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedServiceAccount
     MimeNoContent
     V1ServiceAccountList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts"]
    KubernetesRequest
  ListNamespacedServiceAccount
  MimeNoContent
  V1ServiceAccountList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedServiceAccount
     MimeNoContent
     V1ServiceAccountList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedServiceAccount  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNamespacedServiceAccount AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNamespacedServiceAccount Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> Continue
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNamespacedServiceAccount FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNamespacedServiceAccount LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNamespacedServiceAccount Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> Limit
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedServiceAccount ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNamespacedServiceAccount ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNamespacedServiceAccount SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNamespacedServiceAccount TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNamespacedServiceAccount Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> Watch
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ListNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNamespacedServiceAccount MimeCborSeq
-- | @application/json@
instance Produces ListNamespacedServiceAccount MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNamespacedServiceAccount MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNamespacedServiceAccount MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedServiceAccount MimeYaml


-- *** listNode

-- | @GET \/api\/v1\/nodes@
-- 
-- list or watch objects of kind Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNode
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListNode MimeNoContent V1NodeList accept
listNode :: forall accept.
Accept accept
-> KubernetesRequest ListNode MimeNoContent V1NodeList accept
listNode  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest ListNode MimeNoContent V1NodeList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/nodes"]
    KubernetesRequest ListNode MimeNoContent V1NodeList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ListNode MimeNoContent V1NodeList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNode  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> Pretty -> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListNode AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListNode Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> Continue -> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListNode FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> FieldSelector
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListNode LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> LabelSelector
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListNode Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> Limit -> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNode ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListNode ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListNode SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListNode TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListNode Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListNode contentType res accept
-> Watch -> KubernetesRequest ListNode contentType res accept
applyOptionalParam KubernetesRequest ListNode contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListNode contentType res accept
req KubernetesRequest ListNode contentType res accept
-> [QueryItem] -> KubernetesRequest ListNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListNode MimeCborSeq
-- | @application/json@
instance Produces ListNode MimeJSON
-- | @application/json;stream=watch@
instance Produces ListNode MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListNode MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListNode MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListNode MimeCbor
-- | @application/yaml@
instance Produces ListNode MimeYaml


-- *** listPersistentVolume

-- | @GET \/api\/v1\/persistentvolumes@
-- 
-- list or watch objects of kind PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPersistentVolume
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPersistentVolume MimeNoContent V1PersistentVolumeList accept
listPersistentVolume :: forall accept.
Accept accept
-> KubernetesRequest
     ListPersistentVolume MimeNoContent V1PersistentVolumeList accept
listPersistentVolume  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPersistentVolume MimeNoContent V1PersistentVolumeList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/persistentvolumes"]
    KubernetesRequest
  ListPersistentVolume MimeNoContent V1PersistentVolumeList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPersistentVolume MimeNoContent V1PersistentVolumeList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPersistentVolume  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListPersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListPersistentVolume AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListPersistentVolume Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> Continue
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListPersistentVolume FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> FieldSelector
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListPersistentVolume LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> LabelSelector
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListPersistentVolume Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> Limit
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPersistentVolume ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> ResourceVersion
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPersistentVolume ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListPersistentVolume SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListPersistentVolume TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListPersistentVolume Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPersistentVolume contentType res accept
-> Watch
-> KubernetesRequest ListPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ListPersistentVolume contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListPersistentVolume contentType res accept
req KubernetesRequest ListPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListPersistentVolume MimeCborSeq
-- | @application/json@
instance Produces ListPersistentVolume MimeJSON
-- | @application/json;stream=watch@
instance Produces ListPersistentVolume MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListPersistentVolume MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListPersistentVolume MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListPersistentVolume MimeCbor
-- | @application/yaml@
instance Produces ListPersistentVolume MimeYaml


-- *** listPersistentVolumeClaimForAllNamespaces

-- | @GET \/api\/v1\/persistentvolumeclaims@
-- 
-- list or watch objects of kind PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPersistentVolumeClaimForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces MimeNoContent V1PersistentVolumeClaimList accept
listPersistentVolumeClaimForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
listPersistentVolumeClaimForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/persistentvolumeclaims"]
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces
  MimeNoContent
  V1PersistentVolumeClaimList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces
     MimeNoContent
     V1PersistentVolumeClaimList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPersistentVolumeClaimForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
req KubernetesRequest
  ListPersistentVolumeClaimForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPersistentVolumeClaimForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListPersistentVolumeClaimForAllNamespaces MimeYaml


-- *** listPodForAllNamespaces

-- | @GET \/api\/v1\/pods@
-- 
-- list or watch objects of kind Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPodForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPodForAllNamespaces MimeNoContent V1PodList accept
listPodForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListPodForAllNamespaces MimeNoContent V1PodList accept
listPodForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPodForAllNamespaces MimeNoContent V1PodList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/pods"]
    KubernetesRequest
  ListPodForAllNamespaces MimeNoContent V1PodList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPodForAllNamespaces MimeNoContent V1PodList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPodForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListPodForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListPodForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListPodForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListPodForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListPodForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListPodForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPodForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPodForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListPodForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListPodForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListPodForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListPodForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListPodForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListPodForAllNamespaces contentType res accept
req KubernetesRequest ListPodForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest ListPodForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListPodForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListPodForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListPodForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListPodForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListPodForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListPodForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListPodForAllNamespaces MimeYaml


-- *** listPodTemplateForAllNamespaces

-- | @GET \/api\/v1\/podtemplates@
-- 
-- list or watch objects of kind PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPodTemplateForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPodTemplateForAllNamespaces MimeNoContent V1PodTemplateList accept
listPodTemplateForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListPodTemplateForAllNamespaces
     MimeNoContent
     V1PodTemplateList
     accept
listPodTemplateForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces
     MimeNoContent
     V1PodTemplateList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/podtemplates"]
    KubernetesRequest
  ListPodTemplateForAllNamespaces
  MimeNoContent
  V1PodTemplateList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPodTemplateForAllNamespaces
     MimeNoContent
     V1PodTemplateList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPodTemplateForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListPodTemplateForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListPodTemplateForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListPodTemplateForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListPodTemplateForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListPodTemplateForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListPodTemplateForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPodTemplateForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListPodTemplateForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListPodTemplateForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListPodTemplateForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListPodTemplateForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
req KubernetesRequest
  ListPodTemplateForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListPodTemplateForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListPodTemplateForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListPodTemplateForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListPodTemplateForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListPodTemplateForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListPodTemplateForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListPodTemplateForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListPodTemplateForAllNamespaces MimeYaml


-- *** listReplicationControllerForAllNamespaces

-- | @GET \/api\/v1\/replicationcontrollers@
-- 
-- list or watch objects of kind ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listReplicationControllerForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListReplicationControllerForAllNamespaces MimeNoContent V1ReplicationControllerList accept
listReplicationControllerForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces
     MimeNoContent
     V1ReplicationControllerList
     accept
listReplicationControllerForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces
     MimeNoContent
     V1ReplicationControllerList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/replicationcontrollers"]
    KubernetesRequest
  ListReplicationControllerForAllNamespaces
  MimeNoContent
  V1ReplicationControllerList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces
     MimeNoContent
     V1ReplicationControllerList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListReplicationControllerForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListReplicationControllerForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListReplicationControllerForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListReplicationControllerForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListReplicationControllerForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListReplicationControllerForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListReplicationControllerForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListReplicationControllerForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListReplicationControllerForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListReplicationControllerForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListReplicationControllerForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListReplicationControllerForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
req KubernetesRequest
  ListReplicationControllerForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListReplicationControllerForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListReplicationControllerForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListReplicationControllerForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListReplicationControllerForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListReplicationControllerForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListReplicationControllerForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListReplicationControllerForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListReplicationControllerForAllNamespaces MimeYaml


-- *** listResourceQuotaForAllNamespaces

-- | @GET \/api\/v1\/resourcequotas@
-- 
-- list or watch objects of kind ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceQuotaForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceQuotaForAllNamespaces MimeNoContent V1ResourceQuotaList accept
listResourceQuotaForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces
     MimeNoContent
     V1ResourceQuotaList
     accept
listResourceQuotaForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces
     MimeNoContent
     V1ResourceQuotaList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/resourcequotas"]
    KubernetesRequest
  ListResourceQuotaForAllNamespaces
  MimeNoContent
  V1ResourceQuotaList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces
     MimeNoContent
     V1ResourceQuotaList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListResourceQuotaForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListResourceQuotaForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListResourceQuotaForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListResourceQuotaForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListResourceQuotaForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListResourceQuotaForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListResourceQuotaForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListResourceQuotaForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListResourceQuotaForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListResourceQuotaForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListResourceQuotaForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListResourceQuotaForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
req KubernetesRequest
  ListResourceQuotaForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListResourceQuotaForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListResourceQuotaForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListResourceQuotaForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListResourceQuotaForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListResourceQuotaForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListResourceQuotaForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListResourceQuotaForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListResourceQuotaForAllNamespaces MimeYaml


-- *** listSecretForAllNamespaces

-- | @GET \/api\/v1\/secrets@
-- 
-- list or watch objects of kind Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listSecretForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListSecretForAllNamespaces MimeNoContent V1SecretList accept
listSecretForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListSecretForAllNamespaces MimeNoContent V1SecretList accept
listSecretForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListSecretForAllNamespaces MimeNoContent V1SecretList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/secrets"]
    KubernetesRequest
  ListSecretForAllNamespaces MimeNoContent V1SecretList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListSecretForAllNamespaces MimeNoContent V1SecretList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListSecretForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListSecretForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListSecretForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListSecretForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListSecretForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListSecretForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListSecretForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListSecretForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListSecretForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListSecretForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListSecretForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListSecretForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest ListSecretForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListSecretForAllNamespaces contentType res accept
req KubernetesRequest ListSecretForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListSecretForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListSecretForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListSecretForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListSecretForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListSecretForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListSecretForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListSecretForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListSecretForAllNamespaces MimeYaml


-- *** listServiceAccountForAllNamespaces

-- | @GET \/api\/v1\/serviceaccounts@
-- 
-- list or watch objects of kind ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listServiceAccountForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListServiceAccountForAllNamespaces MimeNoContent V1ServiceAccountList accept
listServiceAccountForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListServiceAccountForAllNamespaces
     MimeNoContent
     V1ServiceAccountList
     accept
listServiceAccountForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces
     MimeNoContent
     V1ServiceAccountList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/serviceaccounts"]
    KubernetesRequest
  ListServiceAccountForAllNamespaces
  MimeNoContent
  V1ServiceAccountList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListServiceAccountForAllNamespaces
     MimeNoContent
     V1ServiceAccountList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListServiceAccountForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListServiceAccountForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListServiceAccountForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListServiceAccountForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListServiceAccountForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListServiceAccountForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListServiceAccountForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceAccountForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceAccountForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListServiceAccountForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListServiceAccountForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListServiceAccountForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceAccountForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceAccountForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListServiceAccountForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListServiceAccountForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListServiceAccountForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListServiceAccountForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListServiceAccountForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListServiceAccountForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListServiceAccountForAllNamespaces MimeYaml


-- *** listServiceForAllNamespaces

-- | @GET \/api\/v1\/services@
-- 
-- list or watch objects of kind Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listServiceForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListServiceForAllNamespaces MimeNoContent V1ServiceList accept
listServiceForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListServiceForAllNamespaces MimeNoContent V1ServiceList accept
listServiceForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListServiceForAllNamespaces MimeNoContent V1ServiceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/services"]
    KubernetesRequest
  ListServiceForAllNamespaces MimeNoContent V1ServiceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListServiceForAllNamespaces MimeNoContent V1ServiceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListServiceForAllNamespaces  

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListServiceForAllNamespaces AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListServiceForAllNamespaces Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListServiceForAllNamespaces FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListServiceForAllNamespaces LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListServiceForAllNamespaces Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListServiceForAllNamespaces Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceForAllNamespaces ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceForAllNamespaces ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListServiceForAllNamespaces SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListServiceForAllNamespaces TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListServiceForAllNamespaces Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
req KubernetesRequest
  ListServiceForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ListServiceForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListServiceForAllNamespaces MimeCborSeq
-- | @application/json@
instance Produces ListServiceForAllNamespaces MimeJSON
-- | @application/json;stream=watch@
instance Produces ListServiceForAllNamespaces MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListServiceForAllNamespaces MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListServiceForAllNamespaces MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListServiceForAllNamespaces MimeCbor
-- | @application/yaml@
instance Produces ListServiceForAllNamespaces MimeYaml


-- *** patchNamespace

-- | @PATCH \/api\/v1\/namespaces\/{name}@
-- 
-- partially update the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespace
  :: (Consumes PatchNamespace contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest PatchNamespace contentType V1Namespace accept
patchNamespace :: forall contentType accept.
(Consumes PatchNamespace contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchNamespace contentType V1Namespace accept
patchNamespace ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest PatchNamespace contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest PatchNamespace contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest PatchNamespace contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNamespace contentType V1Namespace accept
-> Body
-> KubernetesRequest PatchNamespace contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespace contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespace contentType res accept
-> Body -> KubernetesRequest PatchNamespace contentType res accept
`setBodyParam` Body
body

data PatchNamespace 
instance HasBodyParam PatchNamespace Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespace contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespace contentType res accept
applyOptionalParam KubernetesRequest PatchNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespace contentType res accept
req KubernetesRequest PatchNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespace DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespace contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespace contentType res accept
applyOptionalParam KubernetesRequest PatchNamespace contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespace contentType res accept
req KubernetesRequest PatchNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespace FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespace contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespace contentType res accept
applyOptionalParam KubernetesRequest PatchNamespace contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespace contentType res accept
req KubernetesRequest PatchNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespace FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespace contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespace contentType res accept
applyOptionalParam KubernetesRequest PatchNamespace contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespace contentType res accept
req KubernetesRequest PatchNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespace Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespace contentType res accept
-> Force -> KubernetesRequest PatchNamespace contentType res accept
applyOptionalParam KubernetesRequest PatchNamespace contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespace contentType res accept
req KubernetesRequest PatchNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespace MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespace MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespace MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespace MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespace MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespace MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespace MimeCbor
-- | @application/yaml@
instance Produces PatchNamespace MimeYaml


-- *** patchNamespaceStatus

-- | @PATCH \/api\/v1\/namespaces\/{name}\/status@
-- 
-- partially update status of the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespaceStatus
  :: (Consumes PatchNamespaceStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest PatchNamespaceStatus contentType V1Namespace accept
patchNamespaceStatus :: forall contentType accept.
(Consumes PatchNamespaceStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchNamespaceStatus contentType V1Namespace accept
patchNamespaceStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespaceStatus contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespaceStatus contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespaceStatus contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespaceStatus contentType V1Namespace accept
-> Body
-> KubernetesRequest
     PatchNamespaceStatus contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespaceStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespaceStatus contentType res accept
-> Body
-> KubernetesRequest PatchNamespaceStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespaceStatus 
instance HasBodyParam PatchNamespaceStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespaceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespaceStatus contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespaceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespaceStatus contentType res accept
req KubernetesRequest PatchNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespaceStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespaceStatus contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespaceStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespaceStatus contentType res accept
req KubernetesRequest PatchNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespaceStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespaceStatus contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespaceStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespaceStatus contentType res accept
req KubernetesRequest PatchNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespaceStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespaceStatus contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespaceStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespaceStatus contentType res accept
req KubernetesRequest PatchNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespaceStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespaceStatus contentType res accept
-> Force
-> KubernetesRequest PatchNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespaceStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespaceStatus contentType res accept
req KubernetesRequest PatchNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespaceStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespaceStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespaceStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespaceStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespaceStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespaceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespaceStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespaceStatus MimeYaml


-- *** patchNamespacedConfigMap

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/configmaps\/{name}@
-- 
-- partially update the specified ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedConfigMap
  :: (Consumes PatchNamespacedConfigMap contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ConfigMap
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedConfigMap contentType V1ConfigMap accept
patchNamespacedConfigMap :: forall contentType accept.
(Consumes PatchNamespacedConfigMap contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedConfigMap contentType V1ConfigMap accept
patchNamespacedConfigMap ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType V1ConfigMap accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedConfigMap contentType V1ConfigMap accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedConfigMap contentType V1ConfigMap accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedConfigMap contentType V1ConfigMap accept
-> Body
-> KubernetesRequest
     PatchNamespacedConfigMap contentType V1ConfigMap accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedConfigMap contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
`setBodyParam` Body
body

data PatchNamespacedConfigMap 
instance HasBodyParam PatchNamespacedConfigMap Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedConfigMap contentType res accept
req KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedConfigMap DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedConfigMap contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedConfigMap contentType res accept
req KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedConfigMap FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedConfigMap contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedConfigMap contentType res accept
req KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedConfigMap FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedConfigMap contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedConfigMap contentType res accept
req KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedConfigMap Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedConfigMap contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedConfigMap contentType res accept
req KubernetesRequest PatchNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedConfigMap MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedConfigMap MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedConfigMap MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedConfigMap MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedConfigMap MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedConfigMap MimeYaml


-- *** patchNamespacedEndpoints

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/endpoints\/{name}@
-- 
-- partially update the specified Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedEndpoints
  :: (Consumes PatchNamespacedEndpoints contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Endpoints
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedEndpoints contentType V1Endpoints accept
patchNamespacedEndpoints :: forall contentType accept.
(Consumes PatchNamespacedEndpoints contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedEndpoints contentType V1Endpoints accept
patchNamespacedEndpoints ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType V1Endpoints accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedEndpoints contentType V1Endpoints accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedEndpoints contentType V1Endpoints accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedEndpoints contentType V1Endpoints accept
-> Body
-> KubernetesRequest
     PatchNamespacedEndpoints contentType V1Endpoints accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedEndpoints contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
`setBodyParam` Body
body

data PatchNamespacedEndpoints 
instance HasBodyParam PatchNamespacedEndpoints Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedEndpoints contentType res accept
req KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedEndpoints DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEndpoints contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedEndpoints contentType res accept
req KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedEndpoints FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEndpoints contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedEndpoints contentType res accept
req KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedEndpoints FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEndpoints contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedEndpoints contentType res accept
req KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedEndpoints Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEndpoints contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedEndpoints contentType res accept
req KubernetesRequest PatchNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedEndpoints MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedEndpoints MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedEndpoints MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedEndpoints MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedEndpoints MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedEndpoints MimeYaml


-- *** patchNamespacedEvent

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/events\/{name}@
-- 
-- partially update the specified Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedEvent
  :: (Consumes PatchNamespacedEvent contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Event
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedEvent contentType CoreV1Event accept
patchNamespacedEvent :: forall contentType accept.
(Consumes PatchNamespacedEvent contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedEvent contentType CoreV1Event accept
patchNamespacedEvent ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedEvent contentType CoreV1Event accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedEvent contentType CoreV1Event accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedEvent contentType CoreV1Event accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedEvent contentType CoreV1Event accept
-> Body
-> KubernetesRequest
     PatchNamespacedEvent contentType CoreV1Event accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedEvent contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedEvent contentType res accept
-> Body
-> KubernetesRequest PatchNamespacedEvent contentType res accept
`setBodyParam` Body
body

data PatchNamespacedEvent 
instance HasBodyParam PatchNamespacedEvent Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedEvent contentType res accept
req KubernetesRequest PatchNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedEvent DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEvent contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEvent contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedEvent contentType res accept
req KubernetesRequest PatchNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedEvent FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEvent contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEvent contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedEvent contentType res accept
req KubernetesRequest PatchNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedEvent FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEvent contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEvent contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedEvent contentType res accept
req KubernetesRequest PatchNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedEvent Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedEvent contentType res accept
-> Force
-> KubernetesRequest PatchNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedEvent contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedEvent contentType res accept
req KubernetesRequest PatchNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedEvent MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedEvent MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedEvent MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedEvent MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedEvent MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedEvent MimeYaml


-- *** patchNamespacedLimitRange

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/limitranges\/{name}@
-- 
-- partially update the specified LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedLimitRange
  :: (Consumes PatchNamespacedLimitRange contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the LimitRange
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedLimitRange contentType V1LimitRange accept
patchNamespacedLimitRange :: forall contentType accept.
(Consumes PatchNamespacedLimitRange contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedLimitRange contentType V1LimitRange accept
patchNamespacedLimitRange ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType V1LimitRange accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedLimitRange contentType V1LimitRange accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedLimitRange contentType V1LimitRange accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedLimitRange contentType V1LimitRange accept
-> Body
-> KubernetesRequest
     PatchNamespacedLimitRange contentType V1LimitRange accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedLimitRange contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
`setBodyParam` Body
body

data PatchNamespacedLimitRange 
instance HasBodyParam PatchNamespacedLimitRange Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedLimitRange contentType res accept
req KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedLimitRange DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedLimitRange contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedLimitRange contentType res accept
req KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedLimitRange FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedLimitRange contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedLimitRange contentType res accept
req KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedLimitRange FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedLimitRange contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedLimitRange contentType res accept
req KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedLimitRange Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedLimitRange contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedLimitRange contentType res accept
req KubernetesRequest PatchNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedLimitRange MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedLimitRange MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedLimitRange MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedLimitRange MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedLimitRange MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedLimitRange MimeYaml


-- *** patchNamespacedPersistentVolumeClaim

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}@
-- 
-- partially update the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPersistentVolumeClaim
  :: (Consumes PatchNamespacedPersistentVolumeClaim contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType V1PersistentVolumeClaim accept
patchNamespacedPersistentVolumeClaim :: forall contentType accept.
(Consumes PatchNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
patchNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPersistentVolumeClaim 
instance HasBodyParam PatchNamespacedPersistentVolumeClaim Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPersistentVolumeClaim MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaim MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaim MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaim MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPersistentVolumeClaim MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPersistentVolumeClaim MimeYaml


-- *** patchNamespacedPersistentVolumeClaimStatus

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}\/status@
-- 
-- partially update status of the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPersistentVolumeClaimStatus
  :: (Consumes PatchNamespacedPersistentVolumeClaimStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType V1PersistentVolumeClaim accept
patchNamespacedPersistentVolumeClaimStatus :: forall contentType accept.
(Consumes PatchNamespacedPersistentVolumeClaimStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
patchNamespacedPersistentVolumeClaimStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus
  contentType
  V1PersistentVolumeClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPersistentVolumeClaimStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPersistentVolumeClaimStatus 
instance HasBodyParam PatchNamespacedPersistentVolumeClaimStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPersistentVolumeClaimStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaimStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaimStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPersistentVolumeClaimStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPersistentVolumeClaimStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeYaml


-- *** patchNamespacedPod

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}@
-- 
-- partially update the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPod
  :: (Consumes PatchNamespacedPod contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPod contentType V1Pod accept
patchNamespacedPod :: forall contentType accept.
(Consumes PatchNamespacedPod contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest PatchNamespacedPod contentType V1Pod accept
patchNamespacedPod ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest PatchNamespacedPod contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest PatchNamespacedPod contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest PatchNamespacedPod contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNamespacedPod contentType V1Pod accept
-> Body
-> KubernetesRequest PatchNamespacedPod contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPod contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedPod contentType res accept
-> Body
-> KubernetesRequest PatchNamespacedPod contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPod 
instance HasBodyParam PatchNamespacedPod Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedPod contentType res accept
req KubernetesRequest PatchNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPod DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPod contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPod contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedPod contentType res accept
req KubernetesRequest PatchNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPod FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPod contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPod contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedPod contentType res accept
req KubernetesRequest PatchNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPod FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPod contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPod contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedPod contentType res accept
req KubernetesRequest PatchNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPod Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPod contentType res accept
-> Force
-> KubernetesRequest PatchNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPod contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedPod contentType res accept
req KubernetesRequest PatchNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPod MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPod MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPod MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPod MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPod MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPod MimeYaml


-- *** patchNamespacedPodEphemeralcontainers

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/ephemeralcontainers@
-- 
-- partially update ephemeralcontainers of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodEphemeralcontainers
  :: (Consumes PatchNamespacedPodEphemeralcontainers contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
patchNamespacedPodEphemeralcontainers :: forall contentType accept.
(Consumes PatchNamespacedPodEphemeralcontainers contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
patchNamespacedPodEphemeralcontainers ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/ephemeralcontainers"]
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodEphemeralcontainers contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodEphemeralcontainers 
instance HasBodyParam PatchNamespacedPodEphemeralcontainers Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPodEphemeralcontainers Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPodEphemeralcontainers DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPodEphemeralcontainers FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPodEphemeralcontainers FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodEphemeralcontainers Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  PatchNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodEphemeralcontainers MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodEphemeralcontainers MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodEphemeralcontainers MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodEphemeralcontainers MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPodEphemeralcontainers MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPodEphemeralcontainers MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodEphemeralcontainers MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPodEphemeralcontainers MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPodEphemeralcontainers MimeYaml


-- *** patchNamespacedPodResize

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/resize@
-- 
-- partially update resize of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodResize
  :: (Consumes PatchNamespacedPodResize contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodResize contentType V1Pod accept
patchNamespacedPodResize :: forall contentType accept.
(Consumes PatchNamespacedPodResize contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodResize contentType V1Pod accept
patchNamespacedPodResize ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodResize contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/resize"]
    KubernetesRequest PatchNamespacedPodResize contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodResize contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNamespacedPodResize contentType V1Pod accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodResize contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodResize contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodResize 
instance HasBodyParam PatchNamespacedPodResize Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPodResize Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodResize contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedPodResize contentType res accept
req KubernetesRequest PatchNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPodResize DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodResize contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedPodResize contentType res accept
req KubernetesRequest PatchNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPodResize FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodResize contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedPodResize contentType res accept
req KubernetesRequest PatchNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPodResize FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodResize contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedPodResize contentType res accept
req KubernetesRequest PatchNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodResize Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodResize contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodResize contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedPodResize contentType res accept
req KubernetesRequest PatchNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodResize MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodResize MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodResize MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodResize MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPodResize MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPodResize MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodResize MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPodResize MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPodResize MimeYaml


-- *** patchNamespacedPodStatus

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/status@
-- 
-- partially update status of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodStatus
  :: (Consumes PatchNamespacedPodStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodStatus contentType V1Pod accept
patchNamespacedPodStatus :: forall contentType accept.
(Consumes PatchNamespacedPodStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodStatus contentType V1Pod accept
patchNamespacedPodStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest PatchNamespacedPodStatus contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodStatus contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNamespacedPodStatus contentType V1Pod accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodStatus contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodStatus 
instance HasBodyParam PatchNamespacedPodStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPodStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedPodStatus contentType res accept
req KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPodStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedPodStatus contentType res accept
req KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPodStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedPodStatus contentType res accept
req KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPodStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedPodStatus contentType res accept
req KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedPodStatus contentType res accept
req KubernetesRequest PatchNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPodStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPodStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPodStatus MimeYaml


-- *** patchNamespacedPodTemplate

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/podtemplates\/{name}@
-- 
-- partially update the specified PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodTemplate
  :: (Consumes PatchNamespacedPodTemplate contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PodTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodTemplate contentType V1PodTemplate accept
patchNamespacedPodTemplate :: forall contentType accept.
(Consumes PatchNamespacedPodTemplate contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType V1PodTemplate accept
patchNamespacedPodTemplate ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedPodTemplate contentType V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedPodTemplate contentType V1PodTemplate accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType V1PodTemplate accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodTemplate contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodTemplate 
instance HasBodyParam PatchNamespacedPodTemplate Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedPodTemplate DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedPodTemplate FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedPodTemplate FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodTemplate Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedPodTemplate contentType res accept
req KubernetesRequest PatchNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodTemplate MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodTemplate MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodTemplate MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodTemplate MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedPodTemplate MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedPodTemplate MimeYaml


-- *** patchNamespacedReplicationController

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}@
-- 
-- partially update the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedReplicationController
  :: (Consumes PatchNamespacedReplicationController contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedReplicationController contentType V1ReplicationController accept
patchNamespacedReplicationController :: forall contentType accept.
(Consumes PatchNamespacedReplicationController contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
patchNamespacedReplicationController ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedReplicationController contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
`setBodyParam` Body
body

data PatchNamespacedReplicationController 
instance HasBodyParam PatchNamespacedReplicationController Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedReplicationController DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedReplicationController FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedReplicationController FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedReplicationController Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedReplicationController MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedReplicationController MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedReplicationController MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedReplicationController MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedReplicationController MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedReplicationController MimeYaml


-- *** patchNamespacedReplicationControllerScale

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/scale@
-- 
-- partially update scale of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedReplicationControllerScale
  :: (Consumes PatchNamespacedReplicationControllerScale contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Scale
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType V1Scale accept
patchNamespacedReplicationControllerScale :: forall contentType accept.
(Consumes PatchNamespacedReplicationControllerScale contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
patchNamespacedReplicationControllerScale ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
    KubernetesRequest
  PatchNamespacedReplicationControllerScale
  contentType
  V1Scale
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedReplicationControllerScale
  contentType
  V1Scale
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedReplicationControllerScale contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
`setBodyParam` Body
body

data PatchNamespacedReplicationControllerScale 
instance HasBodyParam PatchNamespacedReplicationControllerScale Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedReplicationControllerScale Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedReplicationControllerScale DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedReplicationControllerScale FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedReplicationControllerScale FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedReplicationControllerScale Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedReplicationControllerScale MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedReplicationControllerScale MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedReplicationControllerScale MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedReplicationControllerScale MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedReplicationControllerScale MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedReplicationControllerScale MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedReplicationControllerScale MimeYaml


-- *** patchNamespacedReplicationControllerStatus

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/status@
-- 
-- partially update status of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedReplicationControllerStatus
  :: (Consumes PatchNamespacedReplicationControllerStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType V1ReplicationController accept
patchNamespacedReplicationControllerStatus :: forall contentType accept.
(Consumes PatchNamespacedReplicationControllerStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
patchNamespacedReplicationControllerStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus
  contentType
  V1ReplicationController
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedReplicationControllerStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedReplicationControllerStatus 
instance HasBodyParam PatchNamespacedReplicationControllerStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedReplicationControllerStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedReplicationControllerStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedReplicationControllerStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedReplicationControllerStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  PatchNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedReplicationControllerStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedReplicationControllerStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedReplicationControllerStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedReplicationControllerStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedReplicationControllerStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedReplicationControllerStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedReplicationControllerStatus MimeYaml


-- *** patchNamespacedResourceQuota

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}@
-- 
-- partially update the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceQuota
  :: (Consumes PatchNamespacedResourceQuota contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceQuota contentType V1ResourceQuota accept
patchNamespacedResourceQuota :: forall contentType accept.
(Consumes PatchNamespacedResourceQuota contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType V1ResourceQuota accept
patchNamespacedResourceQuota ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedResourceQuota contentType V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedResourceQuota contentType V1ResourceQuota accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType V1ResourceQuota accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceQuota contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceQuota 
instance HasBodyParam PatchNamespacedResourceQuota Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedResourceQuota DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedResourceQuota FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedResourceQuota FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceQuota Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceQuota MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceQuota MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceQuota MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceQuota MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedResourceQuota MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedResourceQuota MimeYaml


-- *** patchNamespacedResourceQuotaStatus

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}\/status@
-- 
-- partially update status of the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceQuotaStatus
  :: (Consumes PatchNamespacedResourceQuotaStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType V1ResourceQuota accept
patchNamespacedResourceQuotaStatus :: forall contentType accept.
(Consumes PatchNamespacedResourceQuotaStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
patchNamespacedResourceQuotaStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus
  contentType
  V1ResourceQuota
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus
  contentType
  V1ResourceQuota
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceQuotaStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceQuotaStatus 
instance HasBodyParam PatchNamespacedResourceQuotaStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedResourceQuotaStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedResourceQuotaStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedResourceQuotaStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceQuotaStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceQuotaStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceQuotaStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceQuotaStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceQuotaStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedResourceQuotaStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedResourceQuotaStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedResourceQuotaStatus MimeYaml


-- *** patchNamespacedSecret

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/secrets\/{name}@
-- 
-- partially update the specified Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedSecret
  :: (Consumes PatchNamespacedSecret contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Secret
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedSecret contentType V1Secret accept
patchNamespacedSecret :: forall contentType accept.
(Consumes PatchNamespacedSecret contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedSecret contentType V1Secret accept
patchNamespacedSecret ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedSecret contentType V1Secret accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest PatchNamespacedSecret contentType V1Secret accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedSecret contentType V1Secret accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNamespacedSecret contentType V1Secret accept
-> Body
-> KubernetesRequest
     PatchNamespacedSecret contentType V1Secret accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedSecret contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedSecret contentType res accept
-> Body
-> KubernetesRequest PatchNamespacedSecret contentType res accept
`setBodyParam` Body
body

data PatchNamespacedSecret 
instance HasBodyParam PatchNamespacedSecret Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedSecret contentType res accept
req KubernetesRequest PatchNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedSecret DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedSecret contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedSecret contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedSecret contentType res accept
req KubernetesRequest PatchNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedSecret FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedSecret contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedSecret contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedSecret contentType res accept
req KubernetesRequest PatchNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedSecret FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedSecret contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedSecret contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedSecret contentType res accept
req KubernetesRequest PatchNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedSecret Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedSecret contentType res accept
-> Force
-> KubernetesRequest PatchNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedSecret contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedSecret contentType res accept
req KubernetesRequest PatchNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedSecret MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedSecret MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedSecret MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedSecret MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedSecret MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedSecret MimeYaml


-- *** patchNamespacedService

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/services\/{name}@
-- 
-- partially update the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedService
  :: (Consumes PatchNamespacedService contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedService contentType V1Service accept
patchNamespacedService :: forall contentType accept.
(Consumes PatchNamespacedService contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedService contentType V1Service accept
patchNamespacedService ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedService contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedService contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedService contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedService contentType V1Service accept
-> Body
-> KubernetesRequest
     PatchNamespacedService contentType V1Service accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedService contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNamespacedService contentType res accept
-> Body
-> KubernetesRequest PatchNamespacedService contentType res accept
`setBodyParam` Body
body

data PatchNamespacedService 
instance HasBodyParam PatchNamespacedService Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest PatchNamespacedService contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNamespacedService contentType res accept
req KubernetesRequest PatchNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedService DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedService contentType res accept
-> DryRun
-> KubernetesRequest PatchNamespacedService contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedService contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNamespacedService contentType res accept
req KubernetesRequest PatchNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedService FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedService contentType res accept
-> FieldManager
-> KubernetesRequest PatchNamespacedService contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedService contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNamespacedService contentType res accept
req KubernetesRequest PatchNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedService FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedService contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNamespacedService contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedService contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNamespacedService contentType res accept
req KubernetesRequest PatchNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedService Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNamespacedService contentType res accept
-> Force
-> KubernetesRequest PatchNamespacedService contentType res accept
applyOptionalParam KubernetesRequest PatchNamespacedService contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNamespacedService contentType res accept
req KubernetesRequest PatchNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedService MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedService MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedService MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedService MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedService MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedService MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedService MimeYaml


-- *** patchNamespacedServiceAccount

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/serviceaccounts\/{name}@
-- 
-- partially update the specified ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedServiceAccount
  :: (Consumes PatchNamespacedServiceAccount contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceAccount
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedServiceAccount contentType V1ServiceAccount accept
patchNamespacedServiceAccount :: forall contentType accept.
(Consumes PatchNamespacedServiceAccount contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType V1ServiceAccount accept
patchNamespacedServiceAccount ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType V1ServiceAccount accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedServiceAccount contentType V1ServiceAccount accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType V1ServiceAccount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedServiceAccount contentType V1ServiceAccount accept
-> Body
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType V1ServiceAccount accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedServiceAccount contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
`setBodyParam` Body
body

data PatchNamespacedServiceAccount 
instance HasBodyParam PatchNamespacedServiceAccount Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedServiceAccount DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedServiceAccount FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedServiceAccount FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedServiceAccount Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
req KubernetesRequest
  PatchNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedServiceAccount MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedServiceAccount MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedServiceAccount MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedServiceAccount MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedServiceAccount MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedServiceAccount MimeYaml


-- *** patchNamespacedServiceStatus

-- | @PATCH \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/status@
-- 
-- partially update status of the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedServiceStatus
  :: (Consumes PatchNamespacedServiceStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedServiceStatus contentType V1Service accept
patchNamespacedServiceStatus :: forall contentType accept.
(Consumes PatchNamespacedServiceStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType V1Service accept
patchNamespacedServiceStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedServiceStatus contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchNamespacedServiceStatus contentType V1Service accept
-> Body
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType V1Service accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedServiceStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedServiceStatus 
instance HasBodyParam PatchNamespacedServiceStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNamespacedServiceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNamespacedServiceStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNamespacedServiceStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNamespacedServiceStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedServiceStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
req KubernetesRequest
  PatchNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedServiceStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedServiceStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedServiceStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedServiceStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNamespacedServiceStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNamespacedServiceStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNamespacedServiceStatus MimeYaml


-- *** patchNode

-- | @PATCH \/api\/v1\/nodes\/{name}@
-- 
-- partially update the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNode
  :: (Consumes PatchNode contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest PatchNode contentType V1Node accept
patchNode :: forall contentType accept.
(Consumes PatchNode contentType, MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchNode contentType V1Node accept
patchNode ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest PatchNode contentType V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest PatchNode contentType V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest PatchNode contentType V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNode contentType V1Node accept
-> Body -> KubernetesRequest PatchNode contentType V1Node accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNode contentType, MimeRender contentType Body) =>
KubernetesRequest PatchNode contentType res accept
-> Body -> KubernetesRequest PatchNode contentType res accept
`setBodyParam` Body
body

data PatchNode 
instance HasBodyParam PatchNode Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNode contentType res accept
-> Pretty -> KubernetesRequest PatchNode contentType res accept
applyOptionalParam KubernetesRequest PatchNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNode contentType res accept
req KubernetesRequest PatchNode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNode DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNode contentType res accept
-> DryRun -> KubernetesRequest PatchNode contentType res accept
applyOptionalParam KubernetesRequest PatchNode contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNode contentType res accept
req KubernetesRequest PatchNode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNode FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNode contentType res accept
-> FieldManager
-> KubernetesRequest PatchNode contentType res accept
applyOptionalParam KubernetesRequest PatchNode contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNode contentType res accept
req KubernetesRequest PatchNode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNode FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNode contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNode contentType res accept
applyOptionalParam KubernetesRequest PatchNode contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNode contentType res accept
req KubernetesRequest PatchNode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNode Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNode contentType res accept
-> Force -> KubernetesRequest PatchNode contentType res accept
applyOptionalParam KubernetesRequest PatchNode contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNode contentType res accept
req KubernetesRequest PatchNode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNode MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNode MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNode MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNode MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNode MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNode MimeCbor
-- | @application/yaml@
instance Produces PatchNode MimeYaml


-- *** patchNodeStatus

-- | @PATCH \/api\/v1\/nodes\/{name}\/status@
-- 
-- partially update status of the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNodeStatus
  :: (Consumes PatchNodeStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest PatchNodeStatus contentType V1Node accept
patchNodeStatus :: forall contentType accept.
(Consumes PatchNodeStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchNodeStatus contentType V1Node accept
patchNodeStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest PatchNodeStatus contentType V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest PatchNodeStatus contentType V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest PatchNodeStatus contentType V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest PatchNodeStatus contentType V1Node accept
-> Body
-> KubernetesRequest PatchNodeStatus contentType V1Node accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNodeStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchNodeStatus contentType res accept
-> Body -> KubernetesRequest PatchNodeStatus contentType res accept
`setBodyParam` Body
body

data PatchNodeStatus 
instance HasBodyParam PatchNodeStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchNodeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNodeStatus contentType res accept
-> Pretty
-> KubernetesRequest PatchNodeStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNodeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchNodeStatus contentType res accept
req KubernetesRequest PatchNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchNodeStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNodeStatus contentType res accept
-> DryRun
-> KubernetesRequest PatchNodeStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNodeStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchNodeStatus contentType res accept
req KubernetesRequest PatchNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchNodeStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNodeStatus contentType res accept
-> FieldManager
-> KubernetesRequest PatchNodeStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNodeStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchNodeStatus contentType res accept
req KubernetesRequest PatchNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchNodeStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNodeStatus contentType res accept
-> FieldValidation
-> KubernetesRequest PatchNodeStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNodeStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchNodeStatus contentType res accept
req KubernetesRequest PatchNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNodeStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchNodeStatus contentType res accept
-> Force
-> KubernetesRequest PatchNodeStatus contentType res accept
applyOptionalParam KubernetesRequest PatchNodeStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchNodeStatus contentType res accept
req KubernetesRequest PatchNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNodeStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNodeStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNodeStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNodeStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchNodeStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNodeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchNodeStatus MimeCbor
-- | @application/yaml@
instance Produces PatchNodeStatus MimeYaml


-- *** patchPersistentVolume

-- | @PATCH \/api\/v1\/persistentvolumes\/{name}@
-- 
-- partially update the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchPersistentVolume
  :: (Consumes PatchPersistentVolume contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest PatchPersistentVolume contentType V1PersistentVolume accept
patchPersistentVolume :: forall contentType accept.
(Consumes PatchPersistentVolume contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchPersistentVolume contentType V1PersistentVolume accept
patchPersistentVolume ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchPersistentVolume contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchPersistentVolume contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchPersistentVolume contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchPersistentVolume contentType V1PersistentVolume accept
-> Body
-> KubernetesRequest
     PatchPersistentVolume contentType V1PersistentVolume accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchPersistentVolume contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchPersistentVolume contentType res accept
-> Body
-> KubernetesRequest PatchPersistentVolume contentType res accept
`setBodyParam` Body
body

data PatchPersistentVolume 
instance HasBodyParam PatchPersistentVolume Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchPersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchPersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest PatchPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest PatchPersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchPersistentVolume contentType res accept
req KubernetesRequest PatchPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchPersistentVolume DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchPersistentVolume contentType res accept
-> DryRun
-> KubernetesRequest PatchPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest PatchPersistentVolume contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchPersistentVolume contentType res accept
req KubernetesRequest PatchPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchPersistentVolume FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchPersistentVolume contentType res accept
-> FieldManager
-> KubernetesRequest PatchPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest PatchPersistentVolume contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchPersistentVolume contentType res accept
req KubernetesRequest PatchPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchPersistentVolume FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchPersistentVolume contentType res accept
-> FieldValidation
-> KubernetesRequest PatchPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest PatchPersistentVolume contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchPersistentVolume contentType res accept
req KubernetesRequest PatchPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchPersistentVolume Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchPersistentVolume contentType res accept
-> Force
-> KubernetesRequest PatchPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest PatchPersistentVolume contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchPersistentVolume contentType res accept
req KubernetesRequest PatchPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchPersistentVolume MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchPersistentVolume MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchPersistentVolume MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchPersistentVolume MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchPersistentVolume MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchPersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchPersistentVolume MimeCbor
-- | @application/yaml@
instance Produces PatchPersistentVolume MimeYaml


-- *** patchPersistentVolumeStatus

-- | @PATCH \/api\/v1\/persistentvolumes\/{name}\/status@
-- 
-- partially update status of the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchPersistentVolumeStatus
  :: (Consumes PatchPersistentVolumeStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest PatchPersistentVolumeStatus contentType V1PersistentVolume accept
patchPersistentVolumeStatus :: forall contentType accept.
(Consumes PatchPersistentVolumeStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType V1PersistentVolume accept
patchPersistentVolumeStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchPersistentVolumeStatus contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  PatchPersistentVolumeStatus contentType V1PersistentVolume accept
-> Body
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType V1PersistentVolume accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchPersistentVolumeStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
`setBodyParam` Body
body

data PatchPersistentVolumeStatus 
instance HasBodyParam PatchPersistentVolumeStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchPersistentVolumeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> Pretty
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchPersistentVolumeStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> DryRun
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchPersistentVolumeStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchPersistentVolumeStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchPersistentVolumeStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
req KubernetesRequest
  PatchPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchPersistentVolumeStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchPersistentVolumeStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchPersistentVolumeStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchPersistentVolumeStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchPersistentVolumeStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchPersistentVolumeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchPersistentVolumeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchPersistentVolumeStatus MimeCbor
-- | @application/yaml@
instance Produces PatchPersistentVolumeStatus MimeYaml


-- *** readComponentStatus

-- | @GET \/api\/v1\/componentstatuses\/{name}@
-- 
-- read the specified ComponentStatus
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readComponentStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ComponentStatus
  -> KubernetesRequest ReadComponentStatus MimeNoContent V1ComponentStatus accept
readComponentStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadComponentStatus MimeNoContent V1ComponentStatus accept
readComponentStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadComponentStatus MimeNoContent V1ComponentStatus accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/componentstatuses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadComponentStatus MimeNoContent V1ComponentStatus accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadComponentStatus MimeNoContent V1ComponentStatus accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadComponentStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadComponentStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadComponentStatus contentType res accept
-> Pretty
-> KubernetesRequest ReadComponentStatus contentType res accept
applyOptionalParam KubernetesRequest ReadComponentStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadComponentStatus contentType res accept
req KubernetesRequest ReadComponentStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadComponentStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadComponentStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadComponentStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadComponentStatus MimeCbor
-- | @application/yaml@
instance Produces ReadComponentStatus MimeYaml


-- *** readNamespace

-- | @GET \/api\/v1\/namespaces\/{name}@
-- 
-- read the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespace
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest ReadNamespace MimeNoContent V1Namespace accept
readNamespace :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ReadNamespace MimeNoContent V1Namespace accept
readNamespace  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ReadNamespace MimeNoContent V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReadNamespace MimeNoContent V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReadNamespace MimeNoContent V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespace  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespace contentType res accept
-> Pretty -> KubernetesRequest ReadNamespace contentType res accept
applyOptionalParam KubernetesRequest ReadNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespace contentType res accept
req KubernetesRequest ReadNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespace MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespace MimeCbor
-- | @application/yaml@
instance Produces ReadNamespace MimeYaml


-- *** readNamespaceStatus

-- | @GET \/api\/v1\/namespaces\/{name}\/status@
-- 
-- read status of the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespaceStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest ReadNamespaceStatus MimeNoContent V1Namespace accept
readNamespaceStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadNamespaceStatus MimeNoContent V1Namespace accept
readNamespaceStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespaceStatus MimeNoContent V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespaceStatus MimeNoContent V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespaceStatus MimeNoContent V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespaceStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespaceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespaceStatus contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest ReadNamespaceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespaceStatus contentType res accept
req KubernetesRequest ReadNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespaceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespaceStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespaceStatus MimeYaml


-- *** readNamespacedConfigMap

-- | @GET \/api\/v1\/namespaces\/{namespace}\/configmaps\/{name}@
-- 
-- read the specified ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedConfigMap
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ConfigMap
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedConfigMap MimeNoContent V1ConfigMap accept
readNamespacedConfigMap :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedConfigMap MimeNoContent V1ConfigMap accept
readNamespacedConfigMap  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedConfigMap MimeNoContent V1ConfigMap accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedConfigMap MimeNoContent V1ConfigMap accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedConfigMap MimeNoContent V1ConfigMap accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedConfigMap  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedConfigMap contentType res accept
req KubernetesRequest ReadNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedConfigMap MimeYaml


-- *** readNamespacedEndpoints

-- | @GET \/api\/v1\/namespaces\/{namespace}\/endpoints\/{name}@
-- 
-- read the specified Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedEndpoints
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Endpoints
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedEndpoints MimeNoContent V1Endpoints accept
readNamespacedEndpoints :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedEndpoints MimeNoContent V1Endpoints accept
readNamespacedEndpoints  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedEndpoints MimeNoContent V1Endpoints accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedEndpoints MimeNoContent V1Endpoints accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedEndpoints MimeNoContent V1Endpoints accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedEndpoints  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedEndpoints contentType res accept
req KubernetesRequest ReadNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedEndpoints MimeYaml


-- *** readNamespacedEvent

-- | @GET \/api\/v1\/namespaces\/{namespace}\/events\/{name}@
-- 
-- read the specified Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedEvent
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Event
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedEvent MimeNoContent CoreV1Event accept
readNamespacedEvent :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedEvent MimeNoContent CoreV1Event accept
readNamespacedEvent  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedEvent MimeNoContent CoreV1Event accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedEvent MimeNoContent CoreV1Event accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedEvent MimeNoContent CoreV1Event accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedEvent  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedEvent contentType res accept
req KubernetesRequest ReadNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedEvent MimeYaml


-- *** readNamespacedLimitRange

-- | @GET \/api\/v1\/namespaces\/{namespace}\/limitranges\/{name}@
-- 
-- read the specified LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedLimitRange
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the LimitRange
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedLimitRange MimeNoContent V1LimitRange accept
readNamespacedLimitRange :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedLimitRange MimeNoContent V1LimitRange accept
readNamespacedLimitRange  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedLimitRange MimeNoContent V1LimitRange accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedLimitRange MimeNoContent V1LimitRange accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedLimitRange MimeNoContent V1LimitRange accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedLimitRange  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedLimitRange contentType res accept
req KubernetesRequest ReadNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedLimitRange MimeYaml


-- *** readNamespacedPersistentVolumeClaim

-- | @GET \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}@
-- 
-- read the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPersistentVolumeClaim
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPersistentVolumeClaim MimeNoContent V1PersistentVolumeClaim accept
readNamespacedPersistentVolumeClaim :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaim
     accept
readNamespacedPersistentVolumeClaim  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedPersistentVolumeClaim
  MimeNoContent
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaim
     MimeNoContent
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPersistentVolumeClaim  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ReadNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPersistentVolumeClaim MimeYaml


-- *** readNamespacedPersistentVolumeClaimStatus

-- | @GET \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}\/status@
-- 
-- read status of the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPersistentVolumeClaimStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPersistentVolumeClaimStatus MimeNoContent V1PersistentVolumeClaim accept
readNamespacedPersistentVolumeClaimStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaimStatus
     MimeNoContent
     V1PersistentVolumeClaim
     accept
readNamespacedPersistentVolumeClaimStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaimStatus
     MimeNoContent
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedPersistentVolumeClaimStatus
  MimeNoContent
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaimStatus
     MimeNoContent
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPersistentVolumeClaimStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedPersistentVolumeClaimStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedPersistentVolumeClaimStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  ReadNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeYaml


-- *** readNamespacedPod

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}@
-- 
-- read the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPod
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPod MimeNoContent V1Pod accept
readNamespacedPod :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest ReadNamespacedPod MimeNoContent V1Pod accept
readNamespacedPod  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest ReadNamespacedPod MimeNoContent V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReadNamespacedPod MimeNoContent V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReadNamespacedPod MimeNoContent V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPod  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedPod contentType res accept
req KubernetesRequest ReadNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPod MimeYaml


-- *** readNamespacedPodEphemeralcontainers

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/ephemeralcontainers@
-- 
-- read ephemeralcontainers of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodEphemeralcontainers
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodEphemeralcontainers MimeNoContent V1Pod accept
readNamespacedPodEphemeralcontainers :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodEphemeralcontainers MimeNoContent V1Pod accept
readNamespacedPodEphemeralcontainers  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodEphemeralcontainers MimeNoContent V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/ephemeralcontainers"]
    KubernetesRequest
  ReadNamespacedPodEphemeralcontainers MimeNoContent V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodEphemeralcontainers MimeNoContent V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodEphemeralcontainers  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPodEphemeralcontainers Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedPodEphemeralcontainers contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedPodEphemeralcontainers contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  ReadNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPodEphemeralcontainers MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodEphemeralcontainers MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPodEphemeralcontainers MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPodEphemeralcontainers MimeYaml


-- *** readNamespacedPodLog

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/log@
-- 
-- read log of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodLog
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodLog MimeNoContent Text accept
readNamespacedPodLog :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest ReadNamespacedPodLog MimeNoContent Text accept
readNamespacedPodLog  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest ReadNamespacedPodLog MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/log"]
    KubernetesRequest ReadNamespacedPodLog MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReadNamespacedPodLog MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodLog  

-- | /Optional Param/ "container" - The container for which to stream logs. Defaults to only container if there is one container in the pod.
instance HasOptionalParam ReadNamespacedPodLog Container where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Container
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Container Text
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"container", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "follow" - Follow the log stream of the pod. Defaults to false.
instance HasOptionalParam ReadNamespacedPodLog Follow where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Follow
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Follow Bool
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"follow", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "insecureSkipTLSVerifyBackend" - insecureSkipTLSVerifyBackend indicates that the apiserver should not confirm the validity of the serving certificate of the backend it is connecting to.  This will make the HTTPS connection between the apiserver and the backend insecure. This means the apiserver cannot verify the log data it is receiving came from the real kubelet.  If the kubelet is configured to verify the apiserver's TLS credentials, it does not mean the connection to the real kubelet is vulnerable to a man in the middle attack (e.g. an attacker could not intercept the actual log data coming from the real kubelet).
instance HasOptionalParam ReadNamespacedPodLog InsecureSkipTlsVerifyBackend where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> InsecureSkipTlsVerifyBackend
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (InsecureSkipTlsVerifyBackend Bool
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"insecureSkipTLSVerifyBackend", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "limitBytes" - If set, the number of bytes to read from the server before terminating the log output. This may not display a complete final line of logging, and may return slightly more or slightly less than the specified limit.
instance HasOptionalParam ReadNamespacedPodLog LimitBytes where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> LimitBytes
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (LimitBytes Int
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limitBytes", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPodLog Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "previous" - Return previous terminated container logs. Defaults to false.
instance HasOptionalParam ReadNamespacedPodLog Previous where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Previous
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Previous Bool
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"previous", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "sinceSeconds" - A relative time in seconds before the current time from which to show logs. If this value precedes the time a pod was started, only logs since the pod start will be returned. If this value is in the future, no logs will be returned. Only one of sinceSeconds or sinceTime may be specified.
instance HasOptionalParam ReadNamespacedPodLog SinceSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> SinceSeconds
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (SinceSeconds Int
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"sinceSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "stream" - Specify which container log stream to return to the client. Acceptable values are \"All\", \"Stdout\" and \"Stderr\". If not specified, \"All\" is used, and both stdout and stderr are returned interleaved. Note that when \"TailLines\" is specified, \"Stream\" can only be set to nil or \"All\".
instance HasOptionalParam ReadNamespacedPodLog Stream where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Stream
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Stream Text
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"stream", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "tailLines" - If set, the number of lines from the end of the logs to show. If not specified, logs are shown from the creation of the container or sinceSeconds or sinceTime. Note that when \"TailLines\" is specified, \"Stream\" can only be set to nil or \"All\".
instance HasOptionalParam ReadNamespacedPodLog TailLines where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> TailLines
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (TailLines Int
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"tailLines", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "timestamps" - If true, add an RFC3339 or RFC3339Nano timestamp at the beginning of every line of log output. Defaults to false.
instance HasOptionalParam ReadNamespacedPodLog Timestamps where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodLog contentType res accept
-> Timestamps
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodLog contentType res accept
req (Timestamps Bool
xs) =
    KubernetesRequest ReadNamespacedPodLog contentType res accept
req KubernetesRequest ReadNamespacedPodLog contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodLog contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timestamps", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/json@
instance Produces ReadNamespacedPodLog MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodLog MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPodLog MimeCbor
-- | @text/plain@
instance Produces ReadNamespacedPodLog MimePlainText
-- | @application/yaml@
instance Produces ReadNamespacedPodLog MimeYaml


-- *** readNamespacedPodResize

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/resize@
-- 
-- read resize of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodResize
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodResize MimeNoContent V1Pod accept
readNamespacedPodResize :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodResize MimeNoContent V1Pod accept
readNamespacedPodResize  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodResize MimeNoContent V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/resize"]
    KubernetesRequest
  ReadNamespacedPodResize MimeNoContent V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodResize MimeNoContent V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodResize  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPodResize Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodResize contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodResize contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedPodResize contentType res accept
req KubernetesRequest ReadNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPodResize MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodResize MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPodResize MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPodResize MimeYaml


-- *** readNamespacedPodStatus

-- | @GET \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/status@
-- 
-- read status of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodStatus MimeNoContent V1Pod accept
readNamespacedPodStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodStatus MimeNoContent V1Pod accept
readNamespacedPodStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodStatus MimeNoContent V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedPodStatus MimeNoContent V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodStatus MimeNoContent V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPodStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodStatus contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedPodStatus contentType res accept
req KubernetesRequest ReadNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPodStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPodStatus MimeYaml


-- *** readNamespacedPodTemplate

-- | @GET \/api\/v1\/namespaces\/{namespace}\/podtemplates\/{name}@
-- 
-- read the specified PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodTemplate
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodTemplate MimeNoContent V1PodTemplate accept
readNamespacedPodTemplate :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodTemplate MimeNoContent V1PodTemplate accept
readNamespacedPodTemplate  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodTemplate MimeNoContent V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedPodTemplate MimeNoContent V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodTemplate MimeNoContent V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodTemplate  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedPodTemplate contentType res accept
req KubernetesRequest ReadNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedPodTemplate MimeYaml


-- *** readNamespacedReplicationController

-- | @GET \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}@
-- 
-- read the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedReplicationController
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedReplicationController MimeNoContent V1ReplicationController accept
readNamespacedReplicationController :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedReplicationController
     MimeNoContent
     V1ReplicationController
     accept
readNamespacedReplicationController  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedReplicationController
     MimeNoContent
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedReplicationController
  MimeNoContent
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedReplicationController
     MimeNoContent
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationController  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedReplicationController contentType res accept
req KubernetesRequest
  ReadNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedReplicationController MimeYaml


-- *** readNamespacedReplicationControllerScale

-- | @GET \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/scale@
-- 
-- read scale of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedReplicationControllerScale
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Scale
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedReplicationControllerScale MimeNoContent V1Scale accept
readNamespacedReplicationControllerScale :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedReplicationControllerScale
     MimeNoContent
     V1Scale
     accept
readNamespacedReplicationControllerScale  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedReplicationControllerScale
     MimeNoContent
     V1Scale
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
    KubernetesRequest
  ReadNamespacedReplicationControllerScale
  MimeNoContent
  V1Scale
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedReplicationControllerScale
     MimeNoContent
     V1Scale
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationControllerScale  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedReplicationControllerScale Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedReplicationControllerScale contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedReplicationControllerScale contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  ReadNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedReplicationControllerScale MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedReplicationControllerScale MimeYaml


-- *** readNamespacedReplicationControllerStatus

-- | @GET \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/status@
-- 
-- read status of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedReplicationControllerStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedReplicationControllerStatus MimeNoContent V1ReplicationController accept
readNamespacedReplicationControllerStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedReplicationControllerStatus
     MimeNoContent
     V1ReplicationController
     accept
readNamespacedReplicationControllerStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedReplicationControllerStatus
     MimeNoContent
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedReplicationControllerStatus
  MimeNoContent
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedReplicationControllerStatus
     MimeNoContent
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationControllerStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedReplicationControllerStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedReplicationControllerStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  ReadNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedReplicationControllerStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedReplicationControllerStatus MimeYaml


-- *** readNamespacedResourceQuota

-- | @GET \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}@
-- 
-- read the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceQuota
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceQuota MimeNoContent V1ResourceQuota accept
readNamespacedResourceQuota :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceQuota MimeNoContent V1ResourceQuota accept
readNamespacedResourceQuota  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceQuota MimeNoContent V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedResourceQuota MimeNoContent V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceQuota MimeNoContent V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedResourceQuota  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ReadNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedResourceQuota MimeYaml


-- *** readNamespacedResourceQuotaStatus

-- | @GET \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}\/status@
-- 
-- read status of the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceQuotaStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceQuotaStatus MimeNoContent V1ResourceQuota accept
readNamespacedResourceQuotaStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceQuotaStatus
     MimeNoContent
     V1ResourceQuota
     accept
readNamespacedResourceQuotaStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceQuotaStatus
     MimeNoContent
     V1ResourceQuota
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedResourceQuotaStatus
  MimeNoContent
  V1ResourceQuota
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceQuotaStatus
     MimeNoContent
     V1ResourceQuota
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedResourceQuotaStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedResourceQuotaStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedResourceQuotaStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  ReadNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedResourceQuotaStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedResourceQuotaStatus MimeYaml


-- *** readNamespacedSecret

-- | @GET \/api\/v1\/namespaces\/{namespace}\/secrets\/{name}@
-- 
-- read the specified Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedSecret
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Secret
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedSecret MimeNoContent V1Secret accept
readNamespacedSecret :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedSecret MimeNoContent V1Secret accept
readNamespacedSecret  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedSecret MimeNoContent V1Secret accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedSecret MimeNoContent V1Secret accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedSecret MimeNoContent V1Secret accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedSecret  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedSecret contentType res accept
req KubernetesRequest ReadNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedSecret MimeYaml


-- *** readNamespacedService

-- | @GET \/api\/v1\/namespaces\/{namespace}\/services\/{name}@
-- 
-- read the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedService
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedService MimeNoContent V1Service accept
readNamespacedService :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedService MimeNoContent V1Service accept
readNamespacedService  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedService MimeNoContent V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedService MimeNoContent V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedService MimeNoContent V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedService  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest ReadNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ReadNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNamespacedService contentType res accept
req KubernetesRequest ReadNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedService MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedService MimeYaml


-- *** readNamespacedServiceAccount

-- | @GET \/api\/v1\/namespaces\/{namespace}\/serviceaccounts\/{name}@
-- 
-- read the specified ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedServiceAccount
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceAccount
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedServiceAccount MimeNoContent V1ServiceAccount accept
readNamespacedServiceAccount :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedServiceAccount MimeNoContent V1ServiceAccount accept
readNamespacedServiceAccount  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedServiceAccount MimeNoContent V1ServiceAccount accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedServiceAccount MimeNoContent V1ServiceAccount accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedServiceAccount MimeNoContent V1ServiceAccount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedServiceAccount  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ReadNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedServiceAccount MimeYaml


-- *** readNamespacedServiceStatus

-- | @GET \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/status@
-- 
-- read status of the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedServiceStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedServiceStatus MimeNoContent V1Service accept
readNamespacedServiceStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedServiceStatus MimeNoContent V1Service accept
readNamespacedServiceStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedServiceStatus MimeNoContent V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedServiceStatus MimeNoContent V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedServiceStatus MimeNoContent V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedServiceStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNamespacedServiceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReadNamespacedServiceStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReadNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReadNamespacedServiceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReadNamespacedServiceStatus contentType res accept
req KubernetesRequest
  ReadNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNamespacedServiceStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedServiceStatus MimeYaml


-- *** readNode

-- | @GET \/api\/v1\/nodes\/{name}@
-- 
-- read the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNode
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest ReadNode MimeNoContent V1Node accept
readNode :: forall accept.
Accept accept
-> Name -> KubernetesRequest ReadNode MimeNoContent V1Node accept
readNode  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ReadNode MimeNoContent V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReadNode MimeNoContent V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReadNode MimeNoContent V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNode  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNode contentType res accept
-> Pretty -> KubernetesRequest ReadNode contentType res accept
applyOptionalParam KubernetesRequest ReadNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNode contentType res accept
req KubernetesRequest ReadNode contentType res accept
-> [QueryItem] -> KubernetesRequest ReadNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNode MimeCbor
-- | @application/yaml@
instance Produces ReadNode MimeYaml


-- *** readNodeStatus

-- | @GET \/api\/v1\/nodes\/{name}\/status@
-- 
-- read status of the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNodeStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest ReadNodeStatus MimeNoContent V1Node accept
readNodeStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest ReadNodeStatus MimeNoContent V1Node accept
readNodeStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ReadNodeStatus MimeNoContent V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest ReadNodeStatus MimeNoContent V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReadNodeStatus MimeNoContent V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNodeStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadNodeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadNodeStatus contentType res accept
-> Pretty
-> KubernetesRequest ReadNodeStatus contentType res accept
applyOptionalParam KubernetesRequest ReadNodeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadNodeStatus contentType res accept
req KubernetesRequest ReadNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNodeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadNodeStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNodeStatus MimeYaml


-- *** readPersistentVolume

-- | @GET \/api\/v1\/persistentvolumes\/{name}@
-- 
-- read the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readPersistentVolume
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest ReadPersistentVolume MimeNoContent V1PersistentVolume accept
readPersistentVolume :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadPersistentVolume MimeNoContent V1PersistentVolume accept
readPersistentVolume  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadPersistentVolume MimeNoContent V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadPersistentVolume MimeNoContent V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadPersistentVolume MimeNoContent V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadPersistentVolume  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadPersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadPersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest ReadPersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ReadPersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadPersistentVolume contentType res accept
req KubernetesRequest ReadPersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadPersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadPersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadPersistentVolume MimeCbor
-- | @application/yaml@
instance Produces ReadPersistentVolume MimeYaml


-- *** readPersistentVolumeStatus

-- | @GET \/api\/v1\/persistentvolumes\/{name}\/status@
-- 
-- read status of the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readPersistentVolumeStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest ReadPersistentVolumeStatus MimeNoContent V1PersistentVolume accept
readPersistentVolumeStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadPersistentVolumeStatus MimeNoContent V1PersistentVolume accept
readPersistentVolumeStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadPersistentVolumeStatus MimeNoContent V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadPersistentVolumeStatus MimeNoContent V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadPersistentVolumeStatus MimeNoContent V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadPersistentVolumeStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadPersistentVolumeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadPersistentVolumeStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReadPersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest ReadPersistentVolumeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadPersistentVolumeStatus contentType res accept
req KubernetesRequest ReadPersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReadPersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ReadPersistentVolumeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadPersistentVolumeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadPersistentVolumeStatus MimeCbor
-- | @application/yaml@
instance Produces ReadPersistentVolumeStatus MimeYaml


-- *** replaceNamespace

-- | @PUT \/api\/v1\/namespaces\/{name}@
-- 
-- replace the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespace
  :: (Consumes ReplaceNamespace contentType, MimeRender contentType V1Namespace)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Namespace -- ^ "body"
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest ReplaceNamespace contentType V1Namespace accept
replaceNamespace :: forall contentType accept.
(Consumes ReplaceNamespace contentType,
 MimeRender contentType V1Namespace) =>
ContentType contentType
-> Accept accept
-> V1Namespace
-> Name
-> KubernetesRequest
     ReplaceNamespace contentType V1Namespace accept
replaceNamespace ContentType contentType
_  Accept accept
_ V1Namespace
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespace contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReplaceNamespace contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespace contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest ReplaceNamespace contentType V1Namespace accept
-> V1Namespace
-> KubernetesRequest
     ReplaceNamespace contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespace contentType,
 MimeRender contentType V1Namespace) =>
KubernetesRequest ReplaceNamespace contentType res accept
-> V1Namespace
-> KubernetesRequest ReplaceNamespace contentType res accept
`setBodyParam` V1Namespace
body

data ReplaceNamespace 
instance HasBodyParam ReplaceNamespace V1Namespace 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespace Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespace contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNamespace contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespace contentType res accept
req KubernetesRequest ReplaceNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespace DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespace contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNamespace contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespace contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespace contentType res accept
req KubernetesRequest ReplaceNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespace FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespace contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNamespace contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespace contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespace contentType res accept
req KubernetesRequest ReplaceNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespace FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespace contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNamespace contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespace contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespace contentType res accept
req KubernetesRequest ReplaceNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespace mtype

-- | @application/json@
instance Produces ReplaceNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespace MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespace MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespace MimeYaml


-- *** replaceNamespaceFinalize

-- | @PUT \/api\/v1\/namespaces\/{name}\/finalize@
-- 
-- replace finalize of the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespaceFinalize
  :: (Consumes ReplaceNamespaceFinalize contentType, MimeRender contentType V1Namespace)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Namespace -- ^ "body"
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest ReplaceNamespaceFinalize contentType V1Namespace accept
replaceNamespaceFinalize :: forall contentType accept.
(Consumes ReplaceNamespaceFinalize contentType,
 MimeRender contentType V1Namespace) =>
ContentType contentType
-> Accept accept
-> V1Namespace
-> Name
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType V1Namespace accept
replaceNamespaceFinalize ContentType contentType
_  Accept accept
_ V1Namespace
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/finalize"]
    KubernetesRequest
  ReplaceNamespaceFinalize contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespaceFinalize contentType V1Namespace accept
-> V1Namespace
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespaceFinalize contentType,
 MimeRender contentType V1Namespace) =>
KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> V1Namespace
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
`setBodyParam` V1Namespace
body

data ReplaceNamespaceFinalize 
instance HasBodyParam ReplaceNamespaceFinalize V1Namespace 

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespaceFinalize DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespaceFinalize FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespaceFinalize FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespaceFinalize Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespaceFinalize contentType res accept
req KubernetesRequest ReplaceNamespaceFinalize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespaceFinalize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespaceFinalize mtype

-- | @application/json@
instance Produces ReplaceNamespaceFinalize MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespaceFinalize MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespaceFinalize MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespaceFinalize MimeYaml


-- *** replaceNamespaceStatus

-- | @PUT \/api\/v1\/namespaces\/{name}\/status@
-- 
-- replace status of the specified Namespace
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespaceStatus
  :: (Consumes ReplaceNamespaceStatus contentType, MimeRender contentType V1Namespace)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Namespace -- ^ "body"
  -> Name -- ^ "name" -  name of the Namespace
  -> KubernetesRequest ReplaceNamespaceStatus contentType V1Namespace accept
replaceNamespaceStatus :: forall contentType accept.
(Consumes ReplaceNamespaceStatus contentType,
 MimeRender contentType V1Namespace) =>
ContentType contentType
-> Accept accept
-> V1Namespace
-> Name
-> KubernetesRequest
     ReplaceNamespaceStatus contentType V1Namespace accept
replaceNamespaceStatus ContentType contentType
_  Accept accept
_ V1Namespace
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespaceStatus contentType V1Namespace accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespaceStatus contentType V1Namespace accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespaceStatus contentType V1Namespace accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespaceStatus contentType V1Namespace accept
-> V1Namespace
-> KubernetesRequest
     ReplaceNamespaceStatus contentType V1Namespace accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespaceStatus contentType,
 MimeRender contentType V1Namespace) =>
KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> V1Namespace
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
`setBodyParam` V1Namespace
body

data ReplaceNamespaceStatus 
instance HasBodyParam ReplaceNamespaceStatus V1Namespace 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespaceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespaceStatus contentType res accept
req KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespaceStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespaceStatus contentType res accept
req KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespaceStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespaceStatus contentType res accept
req KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespaceStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespaceStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespaceStatus contentType res accept
req KubernetesRequest ReplaceNamespaceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespaceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespaceStatus mtype

-- | @application/json@
instance Produces ReplaceNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespaceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespaceStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespaceStatus MimeYaml


-- *** replaceNamespacedConfigMap

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/configmaps\/{name}@
-- 
-- replace the specified ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedConfigMap
  :: (Consumes ReplaceNamespacedConfigMap contentType, MimeRender contentType V1ConfigMap)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ConfigMap -- ^ "body"
  -> Name -- ^ "name" -  name of the ConfigMap
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedConfigMap contentType V1ConfigMap accept
replaceNamespacedConfigMap :: forall contentType accept.
(Consumes ReplaceNamespacedConfigMap contentType,
 MimeRender contentType V1ConfigMap) =>
ContentType contentType
-> Accept accept
-> V1ConfigMap
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType V1ConfigMap accept
replaceNamespacedConfigMap ContentType contentType
_  Accept accept
_ V1ConfigMap
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType V1ConfigMap accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedConfigMap contentType V1ConfigMap accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType V1ConfigMap accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedConfigMap contentType V1ConfigMap accept
-> V1ConfigMap
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType V1ConfigMap accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedConfigMap contentType,
 MimeRender contentType V1ConfigMap) =>
KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> V1ConfigMap
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
`setBodyParam` V1ConfigMap
body

data ReplaceNamespacedConfigMap 
instance HasBodyParam ReplaceNamespacedConfigMap V1ConfigMap 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedConfigMap Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedConfigMap DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedConfigMap FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedConfigMap FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
req KubernetesRequest ReplaceNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedConfigMap mtype

-- | @application/json@
instance Produces ReplaceNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedConfigMap MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedConfigMap MimeYaml


-- *** replaceNamespacedEndpoints

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/endpoints\/{name}@
-- 
-- replace the specified Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedEndpoints
  :: (Consumes ReplaceNamespacedEndpoints contentType, MimeRender contentType V1Endpoints)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Endpoints -- ^ "body"
  -> Name -- ^ "name" -  name of the Endpoints
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedEndpoints contentType V1Endpoints accept
replaceNamespacedEndpoints :: forall contentType accept.
(Consumes ReplaceNamespacedEndpoints contentType,
 MimeRender contentType V1Endpoints) =>
ContentType contentType
-> Accept accept
-> V1Endpoints
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType V1Endpoints accept
replaceNamespacedEndpoints ContentType contentType
_  Accept accept
_ V1Endpoints
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType V1Endpoints accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedEndpoints contentType V1Endpoints accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType V1Endpoints accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedEndpoints contentType V1Endpoints accept
-> V1Endpoints
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType V1Endpoints accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedEndpoints contentType,
 MimeRender contentType V1Endpoints) =>
KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> V1Endpoints
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
`setBodyParam` V1Endpoints
body

data ReplaceNamespacedEndpoints 
instance HasBodyParam ReplaceNamespacedEndpoints V1Endpoints 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedEndpoints Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedEndpoints DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedEndpoints FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedEndpoints FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
req KubernetesRequest ReplaceNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedEndpoints mtype

-- | @application/json@
instance Produces ReplaceNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedEndpoints MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedEndpoints MimeYaml


-- *** replaceNamespacedEvent

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/events\/{name}@
-- 
-- replace the specified Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedEvent
  :: (Consumes ReplaceNamespacedEvent contentType, MimeRender contentType CoreV1Event)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> CoreV1Event -- ^ "body"
  -> Name -- ^ "name" -  name of the Event
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedEvent contentType CoreV1Event accept
replaceNamespacedEvent :: forall contentType accept.
(Consumes ReplaceNamespacedEvent contentType,
 MimeRender contentType CoreV1Event) =>
ContentType contentType
-> Accept accept
-> CoreV1Event
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedEvent contentType CoreV1Event accept
replaceNamespacedEvent ContentType contentType
_  Accept accept
_ CoreV1Event
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedEvent contentType CoreV1Event accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedEvent contentType CoreV1Event accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedEvent contentType CoreV1Event accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedEvent contentType CoreV1Event accept
-> CoreV1Event
-> KubernetesRequest
     ReplaceNamespacedEvent contentType CoreV1Event accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedEvent contentType,
 MimeRender contentType CoreV1Event) =>
KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> CoreV1Event
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
`setBodyParam` CoreV1Event
body

data ReplaceNamespacedEvent 
instance HasBodyParam ReplaceNamespacedEvent CoreV1Event 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedEvent Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedEvent contentType res accept
req KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedEvent DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEvent contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedEvent contentType res accept
req KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedEvent FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEvent contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedEvent contentType res accept
req KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedEvent FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedEvent contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedEvent contentType res accept
req KubernetesRequest ReplaceNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedEvent mtype

-- | @application/json@
instance Produces ReplaceNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedEvent MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedEvent MimeYaml


-- *** replaceNamespacedLimitRange

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/limitranges\/{name}@
-- 
-- replace the specified LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedLimitRange
  :: (Consumes ReplaceNamespacedLimitRange contentType, MimeRender contentType V1LimitRange)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1LimitRange -- ^ "body"
  -> Name -- ^ "name" -  name of the LimitRange
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedLimitRange contentType V1LimitRange accept
replaceNamespacedLimitRange :: forall contentType accept.
(Consumes ReplaceNamespacedLimitRange contentType,
 MimeRender contentType V1LimitRange) =>
ContentType contentType
-> Accept accept
-> V1LimitRange
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType V1LimitRange accept
replaceNamespacedLimitRange ContentType contentType
_  Accept accept
_ V1LimitRange
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType V1LimitRange accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType V1LimitRange accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType V1LimitRange accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType V1LimitRange accept
-> V1LimitRange
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType V1LimitRange accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedLimitRange contentType,
 MimeRender contentType V1LimitRange) =>
KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> V1LimitRange
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
`setBodyParam` V1LimitRange
body

data ReplaceNamespacedLimitRange 
instance HasBodyParam ReplaceNamespacedLimitRange V1LimitRange 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedLimitRange Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedLimitRange DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedLimitRange FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedLimitRange FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
req KubernetesRequest
  ReplaceNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedLimitRange mtype

-- | @application/json@
instance Produces ReplaceNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedLimitRange MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedLimitRange MimeYaml


-- *** replaceNamespacedPersistentVolumeClaim

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}@
-- 
-- replace the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPersistentVolumeClaim
  :: (Consumes ReplaceNamespacedPersistentVolumeClaim contentType, MimeRender contentType V1PersistentVolumeClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolumeClaim -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType V1PersistentVolumeClaim accept
replaceNamespacedPersistentVolumeClaim :: forall contentType accept.
(Consumes ReplaceNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolumeClaim
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
replaceNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ V1PersistentVolumeClaim
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPersistentVolumeClaim contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
`setBodyParam` V1PersistentVolumeClaim
body

data ReplaceNamespacedPersistentVolumeClaim 
instance HasBodyParam ReplaceNamespacedPersistentVolumeClaim V1PersistentVolumeClaim 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaim FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaim FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPersistentVolumeClaim mtype

-- | @application/json@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeYaml


-- *** replaceNamespacedPersistentVolumeClaimStatus

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims\/{name}\/status@
-- 
-- replace status of the specified PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPersistentVolumeClaimStatus
  :: (Consumes ReplaceNamespacedPersistentVolumeClaimStatus contentType, MimeRender contentType V1PersistentVolumeClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolumeClaim -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolumeClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType V1PersistentVolumeClaim accept
replaceNamespacedPersistentVolumeClaimStatus :: forall contentType accept.
(Consumes ReplaceNamespacedPersistentVolumeClaimStatus contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolumeClaim
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
replaceNamespacedPersistentVolumeClaimStatus ContentType contentType
_  Accept accept
_ V1PersistentVolumeClaim
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus
  contentType
  V1PersistentVolumeClaim
  accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPersistentVolumeClaimStatus contentType,
 MimeRender contentType V1PersistentVolumeClaim) =>
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
`setBodyParam` V1PersistentVolumeClaim
body

data ReplaceNamespacedPersistentVolumeClaimStatus 
instance HasBodyParam ReplaceNamespacedPersistentVolumeClaimStatus V1PersistentVolumeClaim 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPersistentVolumeClaimStatus mtype

-- | @application/json@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeYaml


-- *** replaceNamespacedPod

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}@
-- 
-- replace the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPod
  :: (Consumes ReplaceNamespacedPod contentType, MimeRender contentType V1Pod)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Pod -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
replaceNamespacedPod :: forall contentType accept.
(Consumes ReplaceNamespacedPod contentType,
 MimeRender contentType V1Pod) =>
ContentType contentType
-> Accept accept
-> V1Pod
-> Name
-> Namespace
-> KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
replaceNamespacedPod ContentType contentType
_  Accept accept
_ V1Pod
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
-> V1Pod
-> KubernetesRequest ReplaceNamespacedPod contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPod contentType,
 MimeRender contentType V1Pod) =>
KubernetesRequest ReplaceNamespacedPod contentType res accept
-> V1Pod
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
`setBodyParam` V1Pod
body

data ReplaceNamespacedPod 
instance HasBodyParam ReplaceNamespacedPod V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPod Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedPod contentType res accept
req KubernetesRequest ReplaceNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPod DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPod contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPod contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedPod contentType res accept
req KubernetesRequest ReplaceNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPod FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPod contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPod contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedPod contentType res accept
req KubernetesRequest ReplaceNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPod FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPod contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPod contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedPod contentType res accept
req KubernetesRequest ReplaceNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPod mtype

-- | @application/json@
instance Produces ReplaceNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPod MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPod MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPod MimeYaml


-- *** replaceNamespacedPodEphemeralcontainers

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/ephemeralcontainers@
-- 
-- replace ephemeralcontainers of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodEphemeralcontainers
  :: (Consumes ReplaceNamespacedPodEphemeralcontainers contentType, MimeRender contentType V1Pod)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Pod -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
replaceNamespacedPodEphemeralcontainers :: forall contentType accept.
(Consumes ReplaceNamespacedPodEphemeralcontainers contentType,
 MimeRender contentType V1Pod) =>
ContentType contentType
-> Accept accept
-> V1Pod
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
replaceNamespacedPodEphemeralcontainers ContentType contentType
_  Accept accept
_ V1Pod
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/ephemeralcontainers"]
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodEphemeralcontainers contentType,
 MimeRender contentType V1Pod) =>
KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
`setBodyParam` V1Pod
body

data ReplaceNamespacedPodEphemeralcontainers 
instance HasBodyParam ReplaceNamespacedPodEphemeralcontainers V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPodEphemeralcontainers Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPodEphemeralcontainers DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPodEphemeralcontainers FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPodEphemeralcontainers FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodEphemeralcontainers contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodEphemeralcontainers contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPodEphemeralcontainers mtype

-- | @application/json@
instance Produces ReplaceNamespacedPodEphemeralcontainers MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodEphemeralcontainers MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPodEphemeralcontainers MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPodEphemeralcontainers MimeYaml


-- *** replaceNamespacedPodResize

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/resize@
-- 
-- replace resize of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodResize
  :: (Consumes ReplaceNamespacedPodResize contentType, MimeRender contentType V1Pod)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Pod -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodResize contentType V1Pod accept
replaceNamespacedPodResize :: forall contentType accept.
(Consumes ReplaceNamespacedPodResize contentType,
 MimeRender contentType V1Pod) =>
ContentType contentType
-> Accept accept
-> V1Pod
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType V1Pod accept
replaceNamespacedPodResize ContentType contentType
_  Accept accept
_ V1Pod
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/resize"]
    KubernetesRequest
  ReplaceNamespacedPodResize contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPodResize contentType V1Pod accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodResize contentType,
 MimeRender contentType V1Pod) =>
KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
`setBodyParam` V1Pod
body

data ReplaceNamespacedPodResize 
instance HasBodyParam ReplaceNamespacedPodResize V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPodResize Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPodResize DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPodResize FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPodResize FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedPodResize contentType res accept
req KubernetesRequest ReplaceNamespacedPodResize contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodResize contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPodResize mtype

-- | @application/json@
instance Produces ReplaceNamespacedPodResize MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodResize MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPodResize MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPodResize MimeYaml


-- *** replaceNamespacedPodStatus

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/pods\/{name}\/status@
-- 
-- replace status of the specified Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodStatus
  :: (Consumes ReplaceNamespacedPodStatus contentType, MimeRender contentType V1Pod)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Pod -- ^ "body"
  -> Name -- ^ "name" -  name of the Pod
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodStatus contentType V1Pod accept
replaceNamespacedPodStatus :: forall contentType accept.
(Consumes ReplaceNamespacedPodStatus contentType,
 MimeRender contentType V1Pod) =>
ContentType contentType
-> Accept accept
-> V1Pod
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType V1Pod accept
replaceNamespacedPodStatus ContentType contentType
_  Accept accept
_ V1Pod
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedPodStatus contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPodStatus contentType V1Pod accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodStatus contentType,
 MimeRender contentType V1Pod) =>
KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> V1Pod
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
`setBodyParam` V1Pod
body

data ReplaceNamespacedPodStatus 
instance HasBodyParam ReplaceNamespacedPodStatus V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPodStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPodStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPodStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPodStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
req KubernetesRequest ReplaceNamespacedPodStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPodStatus mtype

-- | @application/json@
instance Produces ReplaceNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPodStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPodStatus MimeYaml


-- *** replaceNamespacedPodTemplate

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/podtemplates\/{name}@
-- 
-- replace the specified PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodTemplate
  :: (Consumes ReplaceNamespacedPodTemplate contentType, MimeRender contentType V1PodTemplate)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PodTemplate -- ^ "body"
  -> Name -- ^ "name" -  name of the PodTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
replaceNamespacedPodTemplate :: forall contentType accept.
(Consumes ReplaceNamespacedPodTemplate contentType,
 MimeRender contentType V1PodTemplate) =>
ContentType contentType
-> Accept accept
-> V1PodTemplate
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
replaceNamespacedPodTemplate ContentType contentType
_  Accept accept
_ V1PodTemplate
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
-> V1PodTemplate
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType V1PodTemplate accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodTemplate contentType,
 MimeRender contentType V1PodTemplate) =>
KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> V1PodTemplate
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
`setBodyParam` V1PodTemplate
body

data ReplaceNamespacedPodTemplate 
instance HasBodyParam ReplaceNamespacedPodTemplate V1PodTemplate 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedPodTemplate Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedPodTemplate DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedPodTemplate FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedPodTemplate FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
req KubernetesRequest
  ReplaceNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedPodTemplate mtype

-- | @application/json@
instance Produces ReplaceNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedPodTemplate MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedPodTemplate MimeYaml


-- *** replaceNamespacedReplicationController

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}@
-- 
-- replace the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedReplicationController
  :: (Consumes ReplaceNamespacedReplicationController contentType, MimeRender contentType V1ReplicationController)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ReplicationController -- ^ "body"
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedReplicationController contentType V1ReplicationController accept
replaceNamespacedReplicationController :: forall contentType accept.
(Consumes ReplaceNamespacedReplicationController contentType,
 MimeRender contentType V1ReplicationController) =>
ContentType contentType
-> Accept accept
-> V1ReplicationController
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
replaceNamespacedReplicationController ContentType contentType
_  Accept accept
_ V1ReplicationController
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> V1ReplicationController
-> KubernetesRequest
     ReplaceNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedReplicationController contentType,
 MimeRender contentType V1ReplicationController) =>
KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> V1ReplicationController
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
`setBodyParam` V1ReplicationController
body

data ReplaceNamespacedReplicationController 
instance HasBodyParam ReplaceNamespacedReplicationController V1ReplicationController 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedReplicationController Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedReplicationController DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedReplicationController FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedReplicationController FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedReplicationController mtype

-- | @application/json@
instance Produces ReplaceNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedReplicationController MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedReplicationController MimeYaml


-- *** replaceNamespacedReplicationControllerScale

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/scale@
-- 
-- replace scale of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedReplicationControllerScale
  :: (Consumes ReplaceNamespacedReplicationControllerScale contentType, MimeRender contentType V1Scale)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Scale -- ^ "body"
  -> Name -- ^ "name" -  name of the Scale
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType V1Scale accept
replaceNamespacedReplicationControllerScale :: forall contentType accept.
(Consumes ReplaceNamespacedReplicationControllerScale contentType,
 MimeRender contentType V1Scale) =>
ContentType contentType
-> Accept accept
-> V1Scale
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
replaceNamespacedReplicationControllerScale ContentType contentType
_  Accept accept
_ V1Scale
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale
  contentType
  V1Scale
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale
  contentType
  V1Scale
  accept
-> V1Scale
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale
     contentType
     V1Scale
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedReplicationControllerScale contentType,
 MimeRender contentType V1Scale) =>
KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> V1Scale
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
`setBodyParam` V1Scale
body

data ReplaceNamespacedReplicationControllerScale 
instance HasBodyParam ReplaceNamespacedReplicationControllerScale V1Scale 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedReplicationControllerScale Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedReplicationControllerScale DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedReplicationControllerScale FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedReplicationControllerScale FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedReplicationControllerScale mtype

-- | @application/json@
instance Produces ReplaceNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedReplicationControllerScale MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedReplicationControllerScale MimeYaml


-- *** replaceNamespacedReplicationControllerStatus

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers\/{name}\/status@
-- 
-- replace status of the specified ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedReplicationControllerStatus
  :: (Consumes ReplaceNamespacedReplicationControllerStatus contentType, MimeRender contentType V1ReplicationController)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ReplicationController -- ^ "body"
  -> Name -- ^ "name" -  name of the ReplicationController
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType V1ReplicationController accept
replaceNamespacedReplicationControllerStatus :: forall contentType accept.
(Consumes ReplaceNamespacedReplicationControllerStatus contentType,
 MimeRender contentType V1ReplicationController) =>
ContentType contentType
-> Accept accept
-> V1ReplicationController
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
replaceNamespacedReplicationControllerStatus ContentType contentType
_  Accept accept
_ V1ReplicationController
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus
  contentType
  V1ReplicationController
  accept
-> V1ReplicationController
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedReplicationControllerStatus contentType,
 MimeRender contentType V1ReplicationController) =>
KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> V1ReplicationController
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
`setBodyParam` V1ReplicationController
body

data ReplaceNamespacedReplicationControllerStatus 
instance HasBodyParam ReplaceNamespacedReplicationControllerStatus V1ReplicationController 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedReplicationControllerStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedReplicationControllerStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedReplicationControllerStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedReplicationControllerStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedReplicationControllerStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedReplicationControllerStatus mtype

-- | @application/json@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeYaml


-- *** replaceNamespacedResourceQuota

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}@
-- 
-- replace the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceQuota
  :: (Consumes ReplaceNamespacedResourceQuota contentType, MimeRender contentType V1ResourceQuota)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ResourceQuota -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
replaceNamespacedResourceQuota :: forall contentType accept.
(Consumes ReplaceNamespacedResourceQuota contentType,
 MimeRender contentType V1ResourceQuota) =>
ContentType contentType
-> Accept accept
-> V1ResourceQuota
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
replaceNamespacedResourceQuota ContentType contentType
_  Accept accept
_ V1ResourceQuota
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
-> V1ResourceQuota
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType V1ResourceQuota accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceQuota contentType,
 MimeRender contentType V1ResourceQuota) =>
KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> V1ResourceQuota
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
`setBodyParam` V1ResourceQuota
body

data ReplaceNamespacedResourceQuota 
instance HasBodyParam ReplaceNamespacedResourceQuota V1ResourceQuota 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedResourceQuota Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedResourceQuota DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedResourceQuota FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedResourceQuota FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedResourceQuota mtype

-- | @application/json@
instance Produces ReplaceNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedResourceQuota MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedResourceQuota MimeYaml


-- *** replaceNamespacedResourceQuotaStatus

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/resourcequotas\/{name}\/status@
-- 
-- replace status of the specified ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceQuotaStatus
  :: (Consumes ReplaceNamespacedResourceQuotaStatus contentType, MimeRender contentType V1ResourceQuota)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ResourceQuota -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceQuota
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType V1ResourceQuota accept
replaceNamespacedResourceQuotaStatus :: forall contentType accept.
(Consumes ReplaceNamespacedResourceQuotaStatus contentType,
 MimeRender contentType V1ResourceQuota) =>
ContentType contentType
-> Accept accept
-> V1ResourceQuota
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
replaceNamespacedResourceQuotaStatus ContentType contentType
_  Accept accept
_ V1ResourceQuota
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus
  contentType
  V1ResourceQuota
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus
  contentType
  V1ResourceQuota
  accept
-> V1ResourceQuota
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus
     contentType
     V1ResourceQuota
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceQuotaStatus contentType,
 MimeRender contentType V1ResourceQuota) =>
KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> V1ResourceQuota
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
`setBodyParam` V1ResourceQuota
body

data ReplaceNamespacedResourceQuotaStatus 
instance HasBodyParam ReplaceNamespacedResourceQuotaStatus V1ResourceQuota 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedResourceQuotaStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedResourceQuotaStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedResourceQuotaStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedResourceQuotaStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedResourceQuotaStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedResourceQuotaStatus mtype

-- | @application/json@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeYaml


-- *** replaceNamespacedSecret

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/secrets\/{name}@
-- 
-- replace the specified Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedSecret
  :: (Consumes ReplaceNamespacedSecret contentType, MimeRender contentType V1Secret)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Secret -- ^ "body"
  -> Name -- ^ "name" -  name of the Secret
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedSecret contentType V1Secret accept
replaceNamespacedSecret :: forall contentType accept.
(Consumes ReplaceNamespacedSecret contentType,
 MimeRender contentType V1Secret) =>
ContentType contentType
-> Accept accept
-> V1Secret
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedSecret contentType V1Secret accept
replaceNamespacedSecret ContentType contentType
_  Accept accept
_ V1Secret
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedSecret contentType V1Secret accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedSecret contentType V1Secret accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedSecret contentType V1Secret accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedSecret contentType V1Secret accept
-> V1Secret
-> KubernetesRequest
     ReplaceNamespacedSecret contentType V1Secret accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedSecret contentType,
 MimeRender contentType V1Secret) =>
KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> V1Secret
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
`setBodyParam` V1Secret
body

data ReplaceNamespacedSecret 
instance HasBodyParam ReplaceNamespacedSecret V1Secret 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedSecret Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedSecret contentType res accept
req KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedSecret DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedSecret contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedSecret contentType res accept
req KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedSecret FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedSecret contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedSecret contentType res accept
req KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedSecret FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedSecret contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedSecret contentType res accept
req KubernetesRequest ReplaceNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedSecret mtype

-- | @application/json@
instance Produces ReplaceNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedSecret MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedSecret MimeYaml


-- *** replaceNamespacedService

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/services\/{name}@
-- 
-- replace the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedService
  :: (Consumes ReplaceNamespacedService contentType, MimeRender contentType V1Service)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Service -- ^ "body"
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedService contentType V1Service accept
replaceNamespacedService :: forall contentType accept.
(Consumes ReplaceNamespacedService contentType,
 MimeRender contentType V1Service) =>
ContentType contentType
-> Accept accept
-> V1Service
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedService contentType V1Service accept
replaceNamespacedService ContentType contentType
_  Accept accept
_ V1Service
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedService contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedService contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedService contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedService contentType V1Service accept
-> V1Service
-> KubernetesRequest
     ReplaceNamespacedService contentType V1Service accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedService contentType,
 MimeRender contentType V1Service) =>
KubernetesRequest ReplaceNamespacedService contentType res accept
-> V1Service
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
`setBodyParam` V1Service
body

data ReplaceNamespacedService 
instance HasBodyParam ReplaceNamespacedService V1Service 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedService Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedService contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedService contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNamespacedService contentType res accept
req KubernetesRequest ReplaceNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedService DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedService contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedService contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNamespacedService contentType res accept
req KubernetesRequest ReplaceNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedService FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedService contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedService contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNamespacedService contentType res accept
req KubernetesRequest ReplaceNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedService FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNamespacedService contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
applyOptionalParam KubernetesRequest ReplaceNamespacedService contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNamespacedService contentType res accept
req KubernetesRequest ReplaceNamespacedService contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedService contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedService mtype

-- | @application/json@
instance Produces ReplaceNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedService MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedService MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedService MimeYaml


-- *** replaceNamespacedServiceAccount

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/serviceaccounts\/{name}@
-- 
-- replace the specified ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedServiceAccount
  :: (Consumes ReplaceNamespacedServiceAccount contentType, MimeRender contentType V1ServiceAccount)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1ServiceAccount -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceAccount
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
replaceNamespacedServiceAccount :: forall contentType accept.
(Consumes ReplaceNamespacedServiceAccount contentType,
 MimeRender contentType V1ServiceAccount) =>
ContentType contentType
-> Accept accept
-> V1ServiceAccount
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
replaceNamespacedServiceAccount ContentType contentType
_  Accept accept
_ V1ServiceAccount
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/serviceaccounts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
-> V1ServiceAccount
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType V1ServiceAccount accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedServiceAccount contentType,
 MimeRender contentType V1ServiceAccount) =>
KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> V1ServiceAccount
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
`setBodyParam` V1ServiceAccount
body

data ReplaceNamespacedServiceAccount 
instance HasBodyParam ReplaceNamespacedServiceAccount V1ServiceAccount 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedServiceAccount Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedServiceAccount DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedServiceAccount FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedServiceAccount FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceAccount contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceAccount contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedServiceAccount mtype

-- | @application/json@
instance Produces ReplaceNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedServiceAccount MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedServiceAccount MimeYaml


-- *** replaceNamespacedServiceStatus

-- | @PUT \/api\/v1\/namespaces\/{namespace}\/services\/{name}\/status@
-- 
-- replace status of the specified Service
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedServiceStatus
  :: (Consumes ReplaceNamespacedServiceStatus contentType, MimeRender contentType V1Service)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Service -- ^ "body"
  -> Name -- ^ "name" -  name of the Service
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedServiceStatus contentType V1Service accept
replaceNamespacedServiceStatus :: forall contentType accept.
(Consumes ReplaceNamespacedServiceStatus contentType,
 MimeRender contentType V1Service) =>
ContentType contentType
-> Accept accept
-> V1Service
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType V1Service accept
replaceNamespacedServiceStatus ContentType contentType
_  Accept accept
_ V1Service
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType V1Service accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/services/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType V1Service accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType V1Service accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType V1Service accept
-> V1Service
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType V1Service accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedServiceStatus contentType,
 MimeRender contentType V1Service) =>
KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> V1Service
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
`setBodyParam` V1Service
body

data ReplaceNamespacedServiceStatus 
instance HasBodyParam ReplaceNamespacedServiceStatus V1Service 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNamespacedServiceStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNamespacedServiceStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNamespacedServiceStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNamespacedServiceStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
req KubernetesRequest
  ReplaceNamespacedServiceStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceNamespacedServiceStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNamespacedServiceStatus mtype

-- | @application/json@
instance Produces ReplaceNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNamespacedServiceStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedServiceStatus MimeYaml


-- *** replaceNode

-- | @PUT \/api\/v1\/nodes\/{name}@
-- 
-- replace the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNode
  :: (Consumes ReplaceNode contentType, MimeRender contentType V1Node)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Node -- ^ "body"
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest ReplaceNode contentType V1Node accept
replaceNode :: forall contentType accept.
(Consumes ReplaceNode contentType,
 MimeRender contentType V1Node) =>
ContentType contentType
-> Accept accept
-> V1Node
-> Name
-> KubernetesRequest ReplaceNode contentType V1Node accept
replaceNode ContentType contentType
_  Accept accept
_ V1Node
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ReplaceNode contentType V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReplaceNode contentType V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReplaceNode contentType V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest ReplaceNode contentType V1Node accept
-> V1Node
-> KubernetesRequest ReplaceNode contentType V1Node accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNode contentType,
 MimeRender contentType V1Node) =>
KubernetesRequest ReplaceNode contentType res accept
-> V1Node -> KubernetesRequest ReplaceNode contentType res accept
`setBodyParam` V1Node
body

data ReplaceNode 
instance HasBodyParam ReplaceNode V1Node 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNode Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNode contentType res accept
-> Pretty -> KubernetesRequest ReplaceNode contentType res accept
applyOptionalParam KubernetesRequest ReplaceNode contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNode contentType res accept
req KubernetesRequest ReplaceNode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNode DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNode contentType res accept
-> DryRun -> KubernetesRequest ReplaceNode contentType res accept
applyOptionalParam KubernetesRequest ReplaceNode contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNode contentType res accept
req KubernetesRequest ReplaceNode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNode FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNode contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNode contentType res accept
applyOptionalParam KubernetesRequest ReplaceNode contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNode contentType res accept
req KubernetesRequest ReplaceNode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNode FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNode contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNode contentType res accept
applyOptionalParam KubernetesRequest ReplaceNode contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNode contentType res accept
req KubernetesRequest ReplaceNode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNode mtype

-- | @application/json@
instance Produces ReplaceNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNode MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNode MimeCbor
-- | @application/yaml@
instance Produces ReplaceNode MimeYaml


-- *** replaceNodeStatus

-- | @PUT \/api\/v1\/nodes\/{name}\/status@
-- 
-- replace status of the specified Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNodeStatus
  :: (Consumes ReplaceNodeStatus contentType, MimeRender contentType V1Node)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Node -- ^ "body"
  -> Name -- ^ "name" -  name of the Node
  -> KubernetesRequest ReplaceNodeStatus contentType V1Node accept
replaceNodeStatus :: forall contentType accept.
(Consumes ReplaceNodeStatus contentType,
 MimeRender contentType V1Node) =>
ContentType contentType
-> Accept accept
-> V1Node
-> Name
-> KubernetesRequest ReplaceNodeStatus contentType V1Node accept
replaceNodeStatus ContentType contentType
_  Accept accept
_ V1Node
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest ReplaceNodeStatus contentType V1Node accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/nodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest ReplaceNodeStatus contentType V1Node accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest ReplaceNodeStatus contentType V1Node accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest ReplaceNodeStatus contentType V1Node accept
-> V1Node
-> KubernetesRequest ReplaceNodeStatus contentType V1Node accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNodeStatus contentType,
 MimeRender contentType V1Node) =>
KubernetesRequest ReplaceNodeStatus contentType res accept
-> V1Node
-> KubernetesRequest ReplaceNodeStatus contentType res accept
`setBodyParam` V1Node
body

data ReplaceNodeStatus 
instance HasBodyParam ReplaceNodeStatus V1Node 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceNodeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNodeStatus contentType res accept
-> Pretty
-> KubernetesRequest ReplaceNodeStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNodeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceNodeStatus contentType res accept
req KubernetesRequest ReplaceNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceNodeStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNodeStatus contentType res accept
-> DryRun
-> KubernetesRequest ReplaceNodeStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNodeStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceNodeStatus contentType res accept
req KubernetesRequest ReplaceNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceNodeStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNodeStatus contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceNodeStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNodeStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceNodeStatus contentType res accept
req KubernetesRequest ReplaceNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceNodeStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceNodeStatus contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceNodeStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceNodeStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceNodeStatus contentType res accept
req KubernetesRequest ReplaceNodeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceNodeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceNodeStatus mtype

-- | @application/json@
instance Produces ReplaceNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNodeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceNodeStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNodeStatus MimeYaml


-- *** replacePersistentVolume

-- | @PUT \/api\/v1\/persistentvolumes\/{name}@
-- 
-- replace the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replacePersistentVolume
  :: (Consumes ReplacePersistentVolume contentType, MimeRender contentType V1PersistentVolume)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolume -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest ReplacePersistentVolume contentType V1PersistentVolume accept
replacePersistentVolume :: forall contentType accept.
(Consumes ReplacePersistentVolume contentType,
 MimeRender contentType V1PersistentVolume) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolume
-> Name
-> KubernetesRequest
     ReplacePersistentVolume contentType V1PersistentVolume accept
replacePersistentVolume ContentType contentType
_  Accept accept
_ V1PersistentVolume
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplacePersistentVolume contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplacePersistentVolume contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplacePersistentVolume contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplacePersistentVolume contentType V1PersistentVolume accept
-> V1PersistentVolume
-> KubernetesRequest
     ReplacePersistentVolume contentType V1PersistentVolume accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplacePersistentVolume contentType,
 MimeRender contentType V1PersistentVolume) =>
KubernetesRequest ReplacePersistentVolume contentType res accept
-> V1PersistentVolume
-> KubernetesRequest ReplacePersistentVolume contentType res accept
`setBodyParam` V1PersistentVolume
body

data ReplacePersistentVolume 
instance HasBodyParam ReplacePersistentVolume V1PersistentVolume 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplacePersistentVolume Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplacePersistentVolume contentType res accept
-> Pretty
-> KubernetesRequest ReplacePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ReplacePersistentVolume contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplacePersistentVolume contentType res accept
req KubernetesRequest ReplacePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplacePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplacePersistentVolume DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplacePersistentVolume contentType res accept
-> DryRun
-> KubernetesRequest ReplacePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ReplacePersistentVolume contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplacePersistentVolume contentType res accept
req KubernetesRequest ReplacePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplacePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplacePersistentVolume FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplacePersistentVolume contentType res accept
-> FieldManager
-> KubernetesRequest ReplacePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ReplacePersistentVolume contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplacePersistentVolume contentType res accept
req KubernetesRequest ReplacePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplacePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplacePersistentVolume FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplacePersistentVolume contentType res accept
-> FieldValidation
-> KubernetesRequest ReplacePersistentVolume contentType res accept
applyOptionalParam KubernetesRequest ReplacePersistentVolume contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplacePersistentVolume contentType res accept
req KubernetesRequest ReplacePersistentVolume contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplacePersistentVolume contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplacePersistentVolume mtype

-- | @application/json@
instance Produces ReplacePersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplacePersistentVolume MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplacePersistentVolume MimeCbor
-- | @application/yaml@
instance Produces ReplacePersistentVolume MimeYaml


-- *** replacePersistentVolumeStatus

-- | @PUT \/api\/v1\/persistentvolumes\/{name}\/status@
-- 
-- replace status of the specified PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replacePersistentVolumeStatus
  :: (Consumes ReplacePersistentVolumeStatus contentType, MimeRender contentType V1PersistentVolume)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PersistentVolume -- ^ "body"
  -> Name -- ^ "name" -  name of the PersistentVolume
  -> KubernetesRequest ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
replacePersistentVolumeStatus :: forall contentType accept.
(Consumes ReplacePersistentVolumeStatus contentType,
 MimeRender contentType V1PersistentVolume) =>
ContentType contentType
-> Accept accept
-> V1PersistentVolume
-> Name
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
replacePersistentVolumeStatus ContentType contentType
_  Accept accept
_ V1PersistentVolume
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/api/v1/persistentvolumes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
-> V1PersistentVolume
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType V1PersistentVolume accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplacePersistentVolumeStatus contentType,
 MimeRender contentType V1PersistentVolume) =>
KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> V1PersistentVolume
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
`setBodyParam` V1PersistentVolume
body

data ReplacePersistentVolumeStatus 
instance HasBodyParam ReplacePersistentVolumeStatus V1PersistentVolume 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplacePersistentVolumeStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplacePersistentVolumeStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplacePersistentVolumeStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplacePersistentVolumeStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
applyOptionalParam KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
req KubernetesRequest
  ReplacePersistentVolumeStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplacePersistentVolumeStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplacePersistentVolumeStatus mtype

-- | @application/json@
instance Produces ReplacePersistentVolumeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplacePersistentVolumeStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplacePersistentVolumeStatus MimeCbor
-- | @application/yaml@
instance Produces ReplacePersistentVolumeStatus MimeYaml