{-
   Kubernetes

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

   OpenAPI Version: 3.0.1
   Kubernetes API version: v1.14.2
   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  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "DELETE" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "DELETE" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/attach"]
    `_hasAuthType` (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 req (Container xs) =
    req `setQuery` toQuery ("container", Just 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 req (Stderr xs) =
    req `setQuery` toQuery ("stderr", Just 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 req (Stdin xs) =
    req `setQuery` toQuery ("stdin", Just 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 req (Stdout xs) =
    req `setQuery` toQuery ("stdout", Just 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 req (Tty xs) =
    req `setQuery` toQuery ("tty", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/exec"]
    `_hasAuthType` (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 req (Command xs) =
    req `setQuery` toQuery ("command", Just 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 req (Container xs) =
    req `setQuery` toQuery ("container", Just xs)

-- | /Optional Param/ "stderr" - Redirect the standard error stream of the pod for this call. Defaults to true.
instance HasOptionalParam ConnectGetNamespacedPodExec Stderr where
  applyOptionalParam req (Stderr xs) =
    req `setQuery` toQuery ("stderr", Just xs)

-- | /Optional Param/ "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectGetNamespacedPodExec Stdin where
  applyOptionalParam req (Stdin xs) =
    req `setQuery` toQuery ("stdin", Just xs)

-- | /Optional Param/ "stdout" - Redirect the standard output stream of the pod for this call. Defaults to true.
instance HasOptionalParam ConnectGetNamespacedPodExec Stdout where
  applyOptionalParam req (Stdout xs) =
    req `setQuery` toQuery ("stdout", Just 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 req (Tty xs) =
    req `setQuery` toQuery ("tty", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/portforward"]
    `_hasAuthType` (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 req (Ports xs) =
    req `setQuery` toQuery ("ports", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "GET" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "HEAD" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "HEAD" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "HEAD" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "HEAD" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "HEAD" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "HEAD" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "OPTIONS" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "OPTIONS" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "OPTIONS" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "OPTIONS" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "OPTIONS" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "OPTIONS" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "PATCH" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "PATCH" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/attach"]
    `_hasAuthType` (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 req (Container xs) =
    req `setQuery` toQuery ("container", Just 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 req (Stderr xs) =
    req `setQuery` toQuery ("stderr", Just 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 req (Stdin xs) =
    req `setQuery` toQuery ("stdin", Just 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 req (Stdout xs) =
    req `setQuery` toQuery ("stdout", Just 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 req (Tty xs) =
    req `setQuery` toQuery ("tty", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/exec"]
    `_hasAuthType` (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 req (Command xs) =
    req `setQuery` toQuery ("command", Just 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 req (Container xs) =
    req `setQuery` toQuery ("container", Just xs)

-- | /Optional Param/ "stderr" - Redirect the standard error stream of the pod for this call. Defaults to true.
instance HasOptionalParam ConnectPostNamespacedPodExec Stderr where
  applyOptionalParam req (Stderr xs) =
    req `setQuery` toQuery ("stderr", Just xs)

-- | /Optional Param/ "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false.
instance HasOptionalParam ConnectPostNamespacedPodExec Stdin where
  applyOptionalParam req (Stdin xs) =
    req `setQuery` toQuery ("stdin", Just xs)

-- | /Optional Param/ "stdout" - Redirect the standard output stream of the pod for this call. Defaults to true.
instance HasOptionalParam ConnectPostNamespacedPodExec Stdout where
  applyOptionalParam req (Stdout xs) =
    req `setQuery` toQuery ("stdout", Just 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 req (Tty xs) =
    req `setQuery` toQuery ("tty", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/portforward"]
    `_hasAuthType` (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 req (Ports xs) =
    req `setQuery` toQuery ("ports", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "POST" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "POST" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Namespace namespace) (Path path) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) =
  _mkRequest "PUT" ["/api/v1/nodes/",toPath name,"/proxy"]
    `_hasAuthType` (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 req (Path xs) =
    req `setQuery` toQuery ("path", Just 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  _ (Name name) (Path path) =
  _mkRequest "PUT" ["/api/v1/nodes/",toPath name,"/proxy/",toPath path]
    `_hasAuthType` (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 req (Path2 xs) =
    req `setQuery` toQuery ("path", Just 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 _  _ body =
  _mkRequest "POST" ["/api/v1/namespaces"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespace
instance HasBodyParam CreateNamespace V1Namespace

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespace MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/bindings"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedBinding Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedBinding MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/configmaps"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedConfigMap
instance HasBodyParam CreateNamespacedConfigMap V1ConfigMap

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/endpoints"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedEndpoints
instance HasBodyParam CreateNamespacedEndpoints V1Endpoints

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

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


-- *** createNamespacedEvent

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

data CreateNamespacedEvent
instance HasBodyParam CreateNamespacedEvent V1Event

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedEvent MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/limitranges"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedLimitRange
instance HasBodyParam CreateNamespacedLimitRange V1LimitRange

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedPersistentVolumeClaim
instance HasBodyParam CreateNamespacedPersistentVolumeClaim V1PersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedPod
instance HasBodyParam CreateNamespacedPod V1Pod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPod MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/binding"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodBinding Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedPodBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodBinding MimeVndKubernetesProtobuf
-- | @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 V1beta1Eviction)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1Eviction -- ^ "body"
  -> Name -- ^ "name" -  name of the Eviction
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPodEviction contentType V1beta1Eviction accept
createNamespacedPodEviction _  _ body (Name name) (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/eviction"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedPodEviction
instance HasBodyParam CreateNamespacedPodEviction V1beta1Eviction

-- | /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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodEviction Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedPodEviction MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodEviction MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/podtemplates"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedPodTemplate
instance HasBodyParam CreateNamespacedPodTemplate V1PodTemplate

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedReplicationController
instance HasBodyParam CreateNamespacedReplicationController V1ReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedResourceQuota
instance HasBodyParam CreateNamespacedResourceQuota V1ResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/secrets"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedSecret
instance HasBodyParam CreateNamespacedSecret V1Secret

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedSecret MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/services"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedService
instance HasBodyParam CreateNamespacedService V1Service

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedService MimeVndKubernetesProtobuf
-- | @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 _  _ body (Namespace namespace) =
  _mkRequest "POST" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNamespacedServiceAccount
instance HasBodyParam CreateNamespacedServiceAccount V1ServiceAccount

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces CreateNamespacedServiceAccount 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 _  _ body =
  _mkRequest "POST" ["/api/v1/nodes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreateNode
instance HasBodyParam CreateNode V1Node

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces CreateNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNode MimeVndKubernetesProtobuf
-- | @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 _  _ body =
  _mkRequest "POST" ["/api/v1/persistentvolumes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data CreatePersistentVolume
instance HasBodyParam CreatePersistentVolume V1PersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreatePersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

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


-- *** deleteCollectionNamespacedConfigMap

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/configmaps@
-- 
-- delete collection of ConfigMap
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedConfigMap
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedConfigMap MimeNoContent V1Status accept
deleteCollectionNamespacedConfigMap  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/configmaps"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedConfigMap

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedConfigMap Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedConfigMap MimeYaml


-- *** deleteCollectionNamespacedEndpoints

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/endpoints@
-- 
-- delete collection of Endpoints
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedEndpoints
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEndpoints MimeNoContent V1Status accept
deleteCollectionNamespacedEndpoints  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/endpoints"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEndpoints

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedEndpoints Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedEndpoints MimeYaml


-- *** deleteCollectionNamespacedEvent

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/events@
-- 
-- delete collection of Event
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedEvent
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEvent MimeNoContent V1Status accept
deleteCollectionNamespacedEvent  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/events"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEvent

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedEvent ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedEvent Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedEvent MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedEvent MimeYaml


-- *** deleteCollectionNamespacedLimitRange

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/limitranges@
-- 
-- delete collection of LimitRange
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedLimitRange
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedLimitRange MimeNoContent V1Status accept
deleteCollectionNamespacedLimitRange  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/limitranges"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedLimitRange

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedLimitRange Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedLimitRange MimeYaml


-- *** deleteCollectionNamespacedPersistentVolumeClaim

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/persistentvolumeclaims@
-- 
-- delete collection of PersistentVolumeClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPersistentVolumeClaim
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim MimeNoContent V1Status accept
deleteCollectionNamespacedPersistentVolumeClaim  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedPersistentVolumeClaim Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPersistentVolumeClaim MimeYaml


-- *** deleteCollectionNamespacedPod

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/pods@
-- 
-- delete collection of Pod
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPod
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPod MimeNoContent V1Status accept
deleteCollectionNamespacedPod  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/pods"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedPod ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedPod Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPod MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPod MimeYaml


-- *** deleteCollectionNamespacedPodTemplate

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/podtemplates@
-- 
-- delete collection of PodTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedPodTemplate
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPodTemplate MimeNoContent V1Status accept
deleteCollectionNamespacedPodTemplate  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/podtemplates"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPodTemplate

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedPodTemplate ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedPodTemplate Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedPodTemplate MimeYaml


-- *** deleteCollectionNamespacedReplicationController

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/replicationcontrollers@
-- 
-- delete collection of ReplicationController
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedReplicationController
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedReplicationController MimeNoContent V1Status accept
deleteCollectionNamespacedReplicationController  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedReplicationController ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedReplicationController Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedReplicationController MimeYaml


-- *** deleteCollectionNamespacedResourceQuota

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/resourcequotas@
-- 
-- delete collection of ResourceQuota
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedResourceQuota
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedResourceQuota MimeNoContent V1Status accept
deleteCollectionNamespacedResourceQuota  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedResourceQuota ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedResourceQuota Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedResourceQuota MimeYaml


-- *** deleteCollectionNamespacedSecret

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/secrets@
-- 
-- delete collection of Secret
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedSecret
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedSecret MimeNoContent V1Status accept
deleteCollectionNamespacedSecret  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/secrets"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedSecret

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedSecret ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedSecret Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedSecret MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedSecret MimeYaml


-- *** deleteCollectionNamespacedServiceAccount

-- | @DELETE \/api\/v1\/namespaces\/{namespace}\/serviceaccounts@
-- 
-- delete collection of ServiceAccount
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNamespacedServiceAccount
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedServiceAccount MimeNoContent V1Status accept
deleteCollectionNamespacedServiceAccount  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedServiceAccount

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNamespacedServiceAccount ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNamespacedServiceAccount Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedServiceAccount MimeYaml


-- *** deleteCollectionNode

-- | @DELETE \/api\/v1\/nodes@
-- 
-- delete collection of Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionNode
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionNode MimeNoContent V1Status accept
deleteCollectionNode  _ =
  _mkRequest "DELETE" ["/api/v1/nodes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNode

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionNode ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionNode Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionNode MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces DeleteCollectionNode MimeYaml


-- *** deleteCollectionPersistentVolume

-- | @DELETE \/api\/v1\/persistentvolumes@
-- 
-- delete collection of PersistentVolume
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionPersistentVolume
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionPersistentVolume MimeNoContent V1Status accept
deleteCollectionPersistentVolume  _ =
  _mkRequest "DELETE" ["/api/v1/persistentvolumes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionPersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteCollectionPersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam DeleteCollectionPersistentVolume ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 DeleteCollectionPersistentVolume Watch where
  applyOptionalParam req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @application/json@
instance Produces DeleteCollectionPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionPersistentVolume MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespace
instance HasBodyParam DeleteNamespace V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespace MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/configmaps/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedConfigMap
instance HasBodyParam DeleteNamespacedConfigMap V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/endpoints/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedEndpoints
instance HasBodyParam DeleteNamespacedEndpoints V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/events/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedEvent
instance HasBodyParam DeleteNamespacedEvent V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedEvent MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/limitranges/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedLimitRange
instance HasBodyParam DeleteNamespacedLimitRange V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedPersistentVolumeClaim _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPersistentVolumeClaim
instance HasBodyParam DeleteNamespacedPersistentVolumeClaim V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedPod _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPod
instance HasBodyParam DeleteNamespacedPod V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPod MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedPodTemplate _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/podtemplates/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedPodTemplate
instance HasBodyParam DeleteNamespacedPodTemplate V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedReplicationController
instance HasBodyParam DeleteNamespacedReplicationController V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedResourceQuota _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedResourceQuota
instance HasBodyParam DeleteNamespacedResourceQuota V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/secrets/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedSecret
instance HasBodyParam DeleteNamespacedSecret V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedSecret MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedService _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedService
instance HasBodyParam DeleteNamespacedService V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedService MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deleteNamespacedServiceAccount _  _ (Name name) (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNamespacedServiceAccount
instance HasBodyParam DeleteNamespacedServiceAccount V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @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 _  _ (Name name) =
  _mkRequest "DELETE" ["/api/v1/nodes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteNode
instance HasBodyParam DeleteNode V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeleteNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeleteNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteNode MimeVndKubernetesProtobuf
-- | @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 V1Status accept
deletePersistentVolume _  _ (Name name) =
  _mkRequest "DELETE" ["/api/v1/persistentvolumes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeletePersistentVolume
instance HasBodyParam DeletePersistentVolume V1DeleteOptions

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam DeletePersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", Just 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 req (OrphanDependents xs) =
    req `setQuery` toQuery ("orphanDependents", Just 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 req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", Just xs)

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

-- | @application/json@
instance Produces DeletePersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeletePersistentVolume MimeVndKubernetesProtobuf
-- | @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  _ =
  _mkRequest "GET" ["/api/v1/"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data GetAPIResources
-- | @application/json@
instance Produces GetAPIResources MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces GetAPIResources MimeVndKubernetesProtobuf
-- | @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  _ =
  _mkRequest "GET" ["/api/v1/componentstatuses"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListComponentStatus

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListComponentStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListComponentStatus ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/configmaps"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListConfigMapForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListConfigMapForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListConfigMapForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/endpoints"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListEndpointsForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListEndpointsForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListEndpointsForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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 V1EventList accept
listEventForAllNamespaces  _ =
  _mkRequest "GET" ["/api/v1/events"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListEventForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListEventForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListEventForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/limitranges"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListLimitRangeForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListLimitRangeForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListLimitRangeForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/namespaces"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespace

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespace ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/configmaps"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedConfigMap

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedConfigMap ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/endpoints"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedEndpoints

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedEndpoints ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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 V1EventList accept
listNamespacedEvent  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/events"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedEvent

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedEvent ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/limitranges"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedLimitRange

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedLimitRange ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedPersistentVolumeClaim ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedPod ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/podtemplates"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedPodTemplate

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedPodTemplate ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedReplicationController ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedResourceQuota ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/secrets"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedSecret

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedSecret ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/services"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedService

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedService ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNamespacedServiceAccount

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNamespacedServiceAccount ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/nodes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListNode

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListNode ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/persistentvolumes"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListPersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListPersistentVolume ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/persistentvolumeclaims"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPersistentVolumeClaimForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListPersistentVolumeClaimForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/pods"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPodForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListPodForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListPodForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/podtemplates"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListPodTemplateForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListPodTemplateForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListPodTemplateForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/replicationcontrollers"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListReplicationControllerForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListReplicationControllerForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListReplicationControllerForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/resourcequotas"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListResourceQuotaForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListResourceQuotaForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListResourceQuotaForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/secrets"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListSecretForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListSecretForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListSecretForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/serviceaccounts"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListServiceAccountForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListServiceAccountForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListServiceAccountForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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  _ =
  _mkRequest "GET" ["/api/v1/services"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ListServiceForAllNamespaces

-- | /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 req (Continue xs) =
    req `setQuery` toQuery ("continue", Just 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 req (FieldSelector xs) =
    req `setQuery` toQuery ("fieldSelector", Just 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 req (LabelSelector xs) =
    req `setQuery` toQuery ("labelSelector", Just 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 req (Limit xs) =
    req `setQuery` toQuery ("limit", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ListServiceForAllNamespaces Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv.
instance HasOptionalParam ListServiceForAllNamespaces ResourceVersion where
  applyOptionalParam req (ResourceVersion xs) =
    req `setQuery` toQuery ("resourceVersion", Just 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 req (TimeoutSeconds xs) =
    req `setQuery` toQuery ("timeoutSeconds", Just 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 req (Watch xs) =
    req `setQuery` toQuery ("watch", Just xs)
-- | @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/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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespace
instance HasBodyParam PatchNamespace Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespace MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespaceStatus
instance HasBodyParam PatchNamespaceStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespaceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespaceStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/configmaps/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedConfigMap
instance HasBodyParam PatchNamespacedConfigMap Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/endpoints/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedEndpoints
instance HasBodyParam PatchNamespacedEndpoints Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @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 V1Event accept
patchNamespacedEvent _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/events/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedEvent
instance HasBodyParam PatchNamespacedEvent Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedEvent MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/limitranges/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedLimitRange
instance HasBodyParam PatchNamespacedLimitRange Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedPersistentVolumeClaim
instance HasBodyParam PatchNamespacedPersistentVolumeClaim Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedPersistentVolumeClaimStatus
instance HasBodyParam PatchNamespacedPersistentVolumeClaimStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedPod
instance HasBodyParam PatchNamespacedPod Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPod MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces PatchNamespacedPod 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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedPodStatus
instance HasBodyParam PatchNamespacedPodStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedPodStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/podtemplates/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedPodTemplate
instance HasBodyParam PatchNamespacedPodTemplate Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedReplicationController
instance HasBodyParam PatchNamespacedReplicationController Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/scale"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedReplicationControllerScale
instance HasBodyParam PatchNamespacedReplicationControllerScale Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedReplicationControllerScale Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedReplicationControllerStatus
instance HasBodyParam PatchNamespacedReplicationControllerStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedResourceQuota
instance HasBodyParam PatchNamespacedResourceQuota Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedResourceQuotaStatus
instance HasBodyParam PatchNamespacedResourceQuotaStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/secrets/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedSecret
instance HasBodyParam PatchNamespacedSecret Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedSecret MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedService
instance HasBodyParam PatchNamespacedService Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedService MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedServiceAccount
instance HasBodyParam PatchNamespacedServiceAccount Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PATCH" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNamespacedServiceStatus
instance HasBodyParam PatchNamespacedServiceStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNamespacedServiceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/nodes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNode
instance HasBodyParam PatchNode Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNode MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/nodes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchNodeStatus
instance HasBodyParam PatchNodeStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchNodeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchNodeStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/persistentvolumes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchPersistentVolume
instance HasBodyParam PatchPersistentVolume Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchPersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchPersistentVolume MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PATCH" ["/api/v1/persistentvolumes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data PatchPersistentVolumeStatus
instance HasBodyParam PatchPersistentVolumeStatus Body

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam PatchPersistentVolumeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just 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 req (Force xs) =
    req `setQuery` toQuery ("force", Just xs)

-- | @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/json@
instance Produces PatchPersistentVolumeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchPersistentVolumeStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/componentstatuses/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadComponentStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadComponentStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadComponentStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadComponentStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespace

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespace Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespace Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespace MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespaceStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespaceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespaceStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/configmaps/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedConfigMap

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedConfigMap Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedConfigMap Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/endpoints/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedEndpoints

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedEndpoints Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedEndpoints Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @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 V1Event accept
readNamespacedEvent  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/events/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedEvent

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedEvent Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedEvent Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedEvent MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/limitranges/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedLimitRange

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedLimitRange Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedLimitRange Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPersistentVolumeClaim Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPersistentVolumeClaim Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPersistentVolumeClaimStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPod Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPod Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPod MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces ReadNamespacedPod 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/log"]
    `_hasAuthType` (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 req (Container xs) =
    req `setQuery` toQuery ("container", Just xs)

-- | /Optional Param/ "follow" - Follow the log stream of the pod. Defaults to false.
instance HasOptionalParam ReadNamespacedPodLog Follow where
  applyOptionalParam req (Follow xs) =
    req `setQuery` toQuery ("follow", Just 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 req (LimitBytes xs) =
    req `setQuery` toQuery ("limitBytes", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPodLog Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "previous" - Return previous terminated container logs. Defaults to false.
instance HasOptionalParam ReadNamespacedPodLog Previous where
  applyOptionalParam req (Previous xs) =
    req `setQuery` toQuery ("previous", Just 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 req (SinceSeconds xs) =
    req `setQuery` toQuery ("sinceSeconds", Just 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
instance HasOptionalParam ReadNamespacedPodLog TailLines where
  applyOptionalParam req (TailLines xs) =
    req `setQuery` toQuery ("tailLines", Just 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 req (Timestamps xs) =
    req `setQuery` toQuery ("timestamps", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPodLog MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodLog MimeVndKubernetesProtobuf
-- | @text/plain@
instance Produces ReadNamespacedPodLog MimePlainText
-- | @application/yaml@
instance Produces ReadNamespacedPodLog 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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPodStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/podtemplates/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedPodTemplate

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPodTemplate Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedPodTemplate Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedReplicationController Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedReplicationController Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/scale"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationControllerScale

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedReplicationControllerScale Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedReplicationControllerStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedResourceQuota Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedResourceQuota Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedResourceQuotaStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/secrets/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedSecret

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedSecret Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedSecret Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedSecret MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedService

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedService Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedService Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedService MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedServiceAccount

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedServiceAccount Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNamespacedServiceAccount Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @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  _ (Name name) (Namespace namespace) =
  _mkRequest "GET" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNamespacedServiceStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNamespacedServiceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/nodes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNode

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNode Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadNode Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNode MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/nodes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadNodeStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadNodeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadNodeStatus MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/persistentvolumes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadPersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadPersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

-- | /Optional Param/ "exact" - Should the export be exact.  Exact export maintains cluster-specific fields like 'Namespace'. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadPersistentVolume Exact where
  applyOptionalParam req (Exact xs) =
    req `setQuery` toQuery ("exact", Just xs)

-- | /Optional Param/ "export" - Should this value be exported.  Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18.
instance HasOptionalParam ReadPersistentVolume Export where
  applyOptionalParam req (Export xs) =
    req `setQuery` toQuery ("export", Just xs)
-- | @application/json@
instance Produces ReadPersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadPersistentVolume MimeVndKubernetesProtobuf
-- | @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  _ (Name name) =
  _mkRequest "GET" ["/api/v1/persistentvolumes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ReadPersistentVolumeStatus

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReadPersistentVolumeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)
-- | @application/json@
instance Produces ReadPersistentVolumeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadPersistentVolumeStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespace
instance HasBodyParam ReplaceNamespace V1Namespace

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespace Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespace MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespace MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath name,"/finalize"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespaceFinalize Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespaceFinalize MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespaceFinalize MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespaceStatus
instance HasBodyParam ReplaceNamespaceStatus V1Namespace

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespaceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespaceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespaceStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/configmaps/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedConfigMap
instance HasBodyParam ReplaceNamespacedConfigMap V1ConfigMap

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedConfigMap Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedConfigMap MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedConfigMap MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/endpoints/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedEndpoints
instance HasBodyParam ReplaceNamespacedEndpoints V1Endpoints

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedEndpoints Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedEndpoints MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedEndpoints MimeVndKubernetesProtobuf
-- | @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 V1Event)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Event -- ^ "body"
  -> Name -- ^ "name" -  name of the Event
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedEvent contentType V1Event accept
replaceNamespacedEvent _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/events/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedEvent
instance HasBodyParam ReplaceNamespacedEvent V1Event

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedEvent Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedEvent MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedEvent MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/limitranges/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedLimitRange
instance HasBodyParam ReplaceNamespacedLimitRange V1LimitRange

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedLimitRange Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedLimitRange MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedLimitRange MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedPersistentVolumeClaim
instance HasBodyParam ReplaceNamespacedPersistentVolumeClaim V1PersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPersistentVolumeClaim MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedPersistentVolumeClaimStatus
instance HasBodyParam ReplaceNamespacedPersistentVolumeClaimStatus V1PersistentVolumeClaim

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPersistentVolumeClaimStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedPod
instance HasBodyParam ReplaceNamespacedPod V1Pod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedPod Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedPod MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPod MimeVndKubernetesProtobuf
-- | @application/yaml@
instance Produces ReplaceNamespacedPod 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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/pods/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedPodStatus
instance HasBodyParam ReplaceNamespacedPodStatus V1Pod

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedPodStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedPodStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/podtemplates/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedPodTemplate
instance HasBodyParam ReplaceNamespacedPodTemplate V1PodTemplate

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedPodTemplate Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedPodTemplate MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedPodTemplate MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedReplicationController
instance HasBodyParam ReplaceNamespacedReplicationController V1ReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedReplicationController Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedReplicationController MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationController MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/scale"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedReplicationControllerScale
instance HasBodyParam ReplaceNamespacedReplicationControllerScale V1Scale

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedReplicationControllerScale Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedReplicationControllerScale MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationControllerScale MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/replicationcontrollers/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedReplicationControllerStatus
instance HasBodyParam ReplaceNamespacedReplicationControllerStatus V1ReplicationController

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedReplicationControllerStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedReplicationControllerStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedResourceQuota
instance HasBodyParam ReplaceNamespacedResourceQuota V1ResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedResourceQuota Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedResourceQuota MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedResourceQuota MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/resourcequotas/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedResourceQuotaStatus
instance HasBodyParam ReplaceNamespacedResourceQuotaStatus V1ResourceQuota

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedResourceQuotaStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedResourceQuotaStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/secrets/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedSecret
instance HasBodyParam ReplaceNamespacedSecret V1Secret

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedSecret Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedSecret MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedSecret MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedService
instance HasBodyParam ReplaceNamespacedService V1Service

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedService Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedService MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedService MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/serviceaccounts/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedServiceAccount
instance HasBodyParam ReplaceNamespacedServiceAccount V1ServiceAccount

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedServiceAccount Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedServiceAccount MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedServiceAccount MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) (Namespace namespace) =
  _mkRequest "PUT" ["/api/v1/namespaces/",toPath namespace,"/services/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNamespacedServiceStatus
instance HasBodyParam ReplaceNamespacedServiceStatus V1Service

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNamespacedServiceStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNamespacedServiceStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNamespacedServiceStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/nodes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNode
instance HasBodyParam ReplaceNode V1Node

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNode Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNode MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNode MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/nodes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplaceNodeStatus
instance HasBodyParam ReplaceNodeStatus V1Node

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplaceNodeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplaceNodeStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceNodeStatus MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/persistentvolumes/",toPath name]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplacePersistentVolume
instance HasBodyParam ReplacePersistentVolume V1PersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplacePersistentVolume Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

-- | @application/json@
instance Produces ReplacePersistentVolume MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplacePersistentVolume MimeVndKubernetesProtobuf
-- | @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 _  _ body (Name name) =
  _mkRequest "PUT" ["/api/v1/persistentvolumes/",toPath name,"/status"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    `setBodyParam` body

data ReplacePersistentVolumeStatus
instance HasBodyParam ReplacePersistentVolumeStatus V1PersistentVolume

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam ReplacePersistentVolumeStatus Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just 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 req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", Just 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 req (FieldManager xs) =
    req `setQuery` toQuery ("fieldManager", Just xs)

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

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