{-
   Kubernetes

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

   OpenAPI Version: 3.0.1
   Kubernetes API version: v1.16.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


-- *** createNamespacedServiceAccountToken

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

data CreateNamespacedServiceAccountToken
instance HasBodyParam CreateNamespacedServiceAccountToken V1TokenRequest

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateNamespacedServiceAccountToken DryRun where
  applyOptionalParam 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 CreateNamespacedServiceAccountToken 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 CreateNamespacedServiceAccountToken Pretty where
  applyOptionalParam req (Pretty xs) =
    req `setQuery` toQuery ("pretty", Just xs)

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

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


-- *** createNode

-- | @POST \/api\/v1\/nodes@
-- 
-- create a Node
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNode
  :: (Consumes CreateNode contentType, MimeRender contentType V1Node)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1Node -- ^ "body"
  -> KubernetesRequest CreateNode contentType V1Node accept
createNode _  _ 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
  :: (Consumes DeleteCollectionNamespacedConfigMap contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType V1Status accept
deleteCollectionNamespacedConfigMap _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/configmaps"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedConfigMap
instance HasBodyParam DeleteCollectionNamespacedConfigMap V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedConfigMap DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedConfigMap OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedConfigMap PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedEndpoints contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType V1Status accept
deleteCollectionNamespacedEndpoints _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/endpoints"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEndpoints
instance HasBodyParam DeleteCollectionNamespacedEndpoints V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedEndpoints DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedEndpoints OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedEndpoints PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedEvent contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedEvent contentType V1Status accept
deleteCollectionNamespacedEvent _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/events"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedEvent
instance HasBodyParam DeleteCollectionNamespacedEvent V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedEvent AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedEvent DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedEvent GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedEvent OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedEvent PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedLimitRange contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType V1Status accept
deleteCollectionNamespacedLimitRange _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/limitranges"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedLimitRange
instance HasBodyParam DeleteCollectionNamespacedLimitRange V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedLimitRange DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedLimitRange OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedLimitRange PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedPersistentVolumeClaim contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType V1Status accept
deleteCollectionNamespacedPersistentVolumeClaim _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/persistentvolumeclaims"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPersistentVolumeClaim
instance HasBodyParam DeleteCollectionNamespacedPersistentVolumeClaim V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedPersistentVolumeClaim PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedPod contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteCollectionNamespacedPod contentType V1Status accept
deleteCollectionNamespacedPod _  _ (Namespace namespace) =
  _mkRequest "DELETE" ["/api/v1/namespaces/",toPath namespace,"/pods"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionNamespacedPod
instance HasBodyParam DeleteCollectionNamespacedPod V1DeleteOptions

-- | /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/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored.  This field is beta.
instance HasOptionalParam DeleteCollectionNamespacedPod AllowWatchBookmarks where
  applyOptionalParam req (AllowWatchBookmarks xs) =
    req `setQuery` toQuery ("allowWatchBookmarks", 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/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionNamespacedPod DryRun where
  applyOptionalParam req (DryRun xs) =
    req `setQuery` toQuery ("dryRun", 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/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionNamespacedPod GracePeriodSeconds where
  applyOptionalParam req (GracePeriodSeconds xs) =
    req `setQuery` toQuery ("gracePeriodSeconds", 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/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionNamespacedPod OrphanDependents where
  applyOptionalParam 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 DeleteCollectionNamespacedPod PropagationPolicy where
  applyOptionalParam req (PropagationPolicy xs) =
    req `setQuery` toQuery ("propagationPolicy", 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)

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

-- | @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
  :: (Consumes DeleteCollectionNamespacedPodTemplate contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  ->