{-
   Kubernetes

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

   OpenAPI Version: 3.0.1
   Kubernetes API version: release-1.16
   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 :: Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
connectDeleteNamespacedPodProxy  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/proxy"]
    KubernetesRequest
  ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ConnectDeleteNamespacedPodProxy MimeNoContent Text accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data ConnectDeleteNamespacedPodProxy  

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


-- *** connectDeleteNamespacedPodProxyWithPath

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

data ConnectDeleteNamespacedPodProxyWithPath  

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


-- *** connectDeleteNamespacedServiceProxy

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

data ConnectDeleteNamespacedServiceProxy  

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


-- *** connectDeleteNamespacedServiceProxyWithPath

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

data ConnectDeleteNamespacedServiceProxyWithPath  

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


-- *** connectDeleteNodeProxy

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

data ConnectDeleteNodeProxy  

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


-- *** connectDeleteNodeProxyWithPath

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

data ConnectDeleteNodeProxyWithPath  

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


-- *** connectGetNamespacedPodAttach

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

data ConnectGetNamespacedPodAttach  

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

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

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

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

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


-- *** connectGetNamespacedPodExec

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

data ConnectGetNamespacedPodExec  

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

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

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

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

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

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


-- *** connectGetNamespacedPodPortforward

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

data ConnectGetNamespacedPodPortforward  

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


-- *** connectGetNamespacedPodProxy

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

data ConnectGetNamespacedPodProxy  

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


-- *** connectGetNamespacedPodProxyWithPath

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

data ConnectGetNamespacedPodProxyWithPath  

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


-- *** connectGetNamespacedServiceProxy

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

data ConnectGetNamespacedServiceProxy  

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


-- *** connectGetNamespacedServiceProxyWithPath

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

data ConnectGetNamespacedServiceProxyWithPath  

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


-- *** connectGetNodeProxy

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

data ConnectGetNodeProxy  

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


-- *** connectGetNodeProxyWithPath

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

data ConnectGetNodeProxyWithPath  

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


-- *** connectHeadNamespacedPodProxy

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

data ConnectHeadNamespacedPodProxy  

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


-- *** connectHeadNamespacedPodProxyWithPath

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

data ConnectHeadNamespacedPodProxyWithPath  

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


-- *** connectHeadNamespacedServiceProxy

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

data ConnectHeadNamespacedServiceProxy  

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


-- *** connectHeadNamespacedServiceProxyWithPath

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

data ConnectHeadNamespacedServiceProxyWithPath  

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


-- *** connectHeadNodeProxy

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

data ConnectHeadNodeProxy  

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


-- *** connectHeadNodeProxyWithPath

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

data ConnectHeadNodeProxyWithPath  

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


-- *** connectOptionsNamespacedPodProxy

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

data ConnectOptionsNamespacedPodProxy  

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


-- *** connectOptionsNamespacedPodProxyWithPath

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

data ConnectOptionsNamespacedPodProxyWithPath  

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


-- *** connectOptionsNamespacedServiceProxy

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

data ConnectOptionsNamespacedServiceProxy  

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


-- *** connectOptionsNamespacedServiceProxyWithPath

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

data ConnectOptionsNamespacedServiceProxyWithPath  

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


-- *** connectOptionsNodeProxy

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

data ConnectOptionsNodeProxy  

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


-- *** connectOptionsNodeProxyWithPath

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

data ConnectOptionsNodeProxyWithPath  

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


-- *** connectPatchNamespacedPodProxy

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

data ConnectPatchNamespacedPodProxy  

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


-- *** connectPatchNamespacedPodProxyWithPath

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

data ConnectPatchNamespacedPodProxyWithPath  

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


-- *** connectPatchNamespacedServiceProxy

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

data ConnectPatchNamespacedServiceProxy  

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


-- *** connectPatchNamespacedServiceProxyWithPath

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

data ConnectPatchNamespacedServiceProxyWithPath  

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


-- *** connectPatchNodeProxy

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

data ConnectPatchNodeProxy  

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


-- *** connectPatchNodeProxyWithPath

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

data ConnectPatchNodeProxyWithPath  

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


-- *** connectPostNamespacedPodAttach

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

data ConnectPostNamespacedPodAttach  

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

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

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

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

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


-- *** connectPostNamespacedPodExec

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

data ConnectPostNamespacedPodExec  

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

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

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

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

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

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


-- *** connectPostNamespacedPodPortforward

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

data ConnectPostNamespacedPodPortforward  

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


-- *** connectPostNamespacedPodProxy

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

data ConnectPostNamespacedPodProxy  

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


-- *** connectPostNamespacedPodProxyWithPath

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

data ConnectPostNamespacedPodProxyWithPath  

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


-- *** connectPostNamespacedServiceProxy

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

data ConnectPostNamespacedServiceProxy  

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


-- *** connectPostNamespacedServiceProxyWithPath

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

data ConnectPostNamespacedServiceProxyWithPath  

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


-- *** connectPostNodeProxy

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

data ConnectPostNodeProxy  

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


-- *** connectPostNodeProxyWithPath

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

data ConnectPostNodeProxyWithPath  

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


-- *** connectPutNamespacedPodProxy

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

data ConnectPutNamespacedPodProxy  

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


-- *** connectPutNamespacedPodProxyWithPath

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

data ConnectPutNamespacedPodProxyWithPath  

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


-- *** connectPutNamespacedServiceProxy

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

data ConnectPutNamespacedServiceProxy  

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


-- *** connectPutNamespacedServiceProxyWithPath

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

data ConnectPutNamespacedServiceProxyWithPath  

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


-- *** connectPutNodeProxy

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

data ConnectPutNodeProxy  

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


-- *** connectPutNodeProxyWithPath

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

data ConnectPutNodeProxyWithPath  

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


-- *** createNamespace

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

data CreateNamespace 
instance HasBodyParam CreateNamespace V1Namespace 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespace Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespace contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespace FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespace contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespace contentType res accept
applyOptionalParam KubernetesRequest CreateNamespace contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespace contentType res accept
req KubernetesRequest CreateNamespace contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespace contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Binding
-> Namespace
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
createNamespacedBinding ContentType contentType
_  Accept accept
_ V1Binding
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/bindings"]
    KubernetesRequest
  CreateNamespacedBinding contentType V1Binding accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedBinding contentType V1Binding accept
-> V1Binding
-> KubernetesRequest
     CreateNamespacedBinding contentType V1Binding accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Binding
body

data CreateNamespacedBinding 
instance HasBodyParam CreateNamespacedBinding V1Binding 

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

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

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedBinding Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedBinding contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedBinding contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedBinding contentType res accept
req KubernetesRequest CreateNamespacedBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedBinding mtype

-- | @application/json@
instance Produces CreateNamespacedBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedBinding MimeVndKubernetesProtobuf
-- | @application/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 :: ContentType contentType
-> Accept accept
-> V1ConfigMap
-> Namespace
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
createNamespacedConfigMap ContentType contentType
_  Accept accept
_ V1ConfigMap
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/configmaps"]
    KubernetesRequest
  CreateNamespacedConfigMap contentType V1ConfigMap accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedConfigMap contentType V1ConfigMap accept
-> V1ConfigMap
-> KubernetesRequest
     CreateNamespacedConfigMap contentType V1ConfigMap accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1ConfigMap
body

data CreateNamespacedConfigMap 
instance HasBodyParam CreateNamespacedConfigMap V1ConfigMap 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedConfigMap Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedConfigMap FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedConfigMap contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedConfigMap contentType res accept
req KubernetesRequest CreateNamespacedConfigMap contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedConfigMap contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Endpoints
-> Namespace
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
createNamespacedEndpoints ContentType contentType
_  Accept accept
_ V1Endpoints
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/endpoints"]
    KubernetesRequest
  CreateNamespacedEndpoints contentType V1Endpoints accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedEndpoints contentType V1Endpoints accept
-> V1Endpoints
-> KubernetesRequest
     CreateNamespacedEndpoints contentType V1Endpoints accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Endpoints
body

data CreateNamespacedEndpoints 
instance HasBodyParam CreateNamespacedEndpoints V1Endpoints 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedEndpoints Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedEndpoints FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEndpoints contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedEndpoints contentType res accept
req KubernetesRequest CreateNamespacedEndpoints contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedEndpoints contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Event
-> Namespace
-> KubernetesRequest
     CreateNamespacedEvent contentType V1Event accept
createNamespacedEvent ContentType contentType
_  Accept accept
_ V1Event
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedEvent contentType V1Event accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/events"]
    KubernetesRequest CreateNamespacedEvent contentType V1Event accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedEvent contentType V1Event accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest CreateNamespacedEvent contentType V1Event accept
-> V1Event
-> KubernetesRequest
     CreateNamespacedEvent contentType V1Event accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Event
body

data CreateNamespacedEvent 
instance HasBodyParam CreateNamespacedEvent V1Event 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedEvent Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedEvent FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedEvent contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedEvent contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedEvent contentType res accept
req KubernetesRequest CreateNamespacedEvent contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedEvent contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1LimitRange
-> Namespace
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
createNamespacedLimitRange ContentType contentType
_  Accept accept
_ V1LimitRange
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/limitranges"]
    KubernetesRequest
  CreateNamespacedLimitRange contentType V1LimitRange accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedLimitRange contentType V1LimitRange accept
-> V1LimitRange
-> KubernetesRequest
     CreateNamespacedLimitRange contentType V1LimitRange accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1LimitRange
body

data CreateNamespacedLimitRange 
instance HasBodyParam CreateNamespacedLimitRange V1LimitRange 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedLimitRange Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedLimitRange FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedLimitRange contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedLimitRange contentType res accept
req KubernetesRequest CreateNamespacedLimitRange contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedLimitRange contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1PersistentVolumeClaim
-> Namespace
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
createNamespacedPersistentVolumeClaim ContentType contentType
_  Accept accept
_ V1PersistentVolumeClaim
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/persistentvolumeclaims"]
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim
  contentType
  V1PersistentVolumeClaim
  accept
-> V1PersistentVolumeClaim
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim
     contentType
     V1PersistentVolumeClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1PersistentVolumeClaim
body

data CreateNamespacedPersistentVolumeClaim 
instance HasBodyParam CreateNamespacedPersistentVolumeClaim V1PersistentVolumeClaim 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim Pretty where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPersistentVolumeClaim FieldManager where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
req KubernetesRequest
  CreateNamespacedPersistentVolumeClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPersistentVolumeClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Pod
-> Namespace
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
createNamespacedPod ContentType contentType
_  Accept accept
_ V1Pod
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods"]
    KubernetesRequest CreateNamespacedPod contentType V1Pod accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest CreateNamespacedPod contentType V1Pod accept
-> V1Pod
-> KubernetesRequest CreateNamespacedPod contentType V1Pod accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Pod
body

data CreateNamespacedPod 
instance HasBodyParam CreateNamespacedPod V1Pod 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPod Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedPod contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPod FieldManager where
  applyOptionalParam :: KubernetesRequest CreateNamespacedPod contentType res accept
-> FieldManager
-> KubernetesRequest CreateNamespacedPod contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPod contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateNamespacedPod contentType res accept
req KubernetesRequest CreateNamespacedPod contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedPod contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Binding
-> Name
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
createNamespacedPodBinding ContentType contentType
_  Accept accept
_ V1Binding
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/binding"]
    KubernetesRequest
  CreateNamespacedPodBinding contentType V1Binding accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodBinding contentType V1Binding accept
-> V1Binding
-> KubernetesRequest
     CreateNamespacedPodBinding contentType V1Binding accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Binding
body

data CreateNamespacedPodBinding 
instance HasBodyParam CreateNamespacedPodBinding V1Binding 

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

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

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodBinding Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedPodBinding contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedPodBinding contentType res accept
req KubernetesRequest CreateNamespacedPodBinding contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodBinding contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPodBinding mtype

-- | @application/json@
instance Produces CreateNamespacedPodBinding MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodBinding MimeVndKubernetesProtobuf
-- | @application/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 :: ContentType contentType
-> Accept accept
-> V1beta1Eviction
-> Name
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1beta1Eviction accept
createNamespacedPodEviction ContentType contentType
_  Accept accept
_ V1beta1Eviction
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1beta1Eviction accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/pods/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/eviction"]
    KubernetesRequest
  CreateNamespacedPodEviction contentType V1beta1Eviction accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1beta1Eviction accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodEviction contentType V1beta1Eviction accept
-> V1beta1Eviction
-> KubernetesRequest
     CreateNamespacedPodEviction contentType V1beta1Eviction accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1Eviction
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 :: KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> DryRun
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodEviction Pretty where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
req KubernetesRequest
  CreateNamespacedPodEviction contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodEviction contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
instance MimeType mtype => Consumes CreateNamespacedPodEviction mtype

-- | @application/json@
instance Produces CreateNamespacedPodEviction MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateNamespacedPodEviction MimeVndKubernetesProtobuf
-- | @application/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 :: ContentType contentType
-> Accept accept
-> V1PodTemplate
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
createNamespacedPodTemplate ContentType contentType
_  Accept accept
_ V1PodTemplate
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podtemplates"]
    KubernetesRequest
  CreateNamespacedPodTemplate contentType V1PodTemplate accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedPodTemplate contentType V1PodTemplate accept
-> V1PodTemplate
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType V1PodTemplate accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1PodTemplate
body

data CreateNamespacedPodTemplate 
instance HasBodyParam CreateNamespacedPodTemplate V1PodTemplate 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedPodTemplate Pretty where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedPodTemplate FieldManager where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
req KubernetesRequest
  CreateNamespacedPodTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedPodTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1ReplicationController
-> Namespace
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
createNamespacedReplicationController ContentType contentType
_  Accept accept
_ V1ReplicationController
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicationcontrollers"]
    KubernetesRequest
  CreateNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedReplicationController
  contentType
  V1ReplicationController
  accept
-> V1ReplicationController
-> KubernetesRequest
     CreateNamespacedReplicationController
     contentType
     V1ReplicationController
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1ReplicationController
body

data CreateNamespacedReplicationController 
instance HasBodyParam CreateNamespacedReplicationController V1ReplicationController 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedReplicationController Pretty where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedReplicationController FieldManager where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
req KubernetesRequest
  CreateNamespacedReplicationController contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedReplicationController contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1ResourceQuota
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
createNamespacedResourceQuota ContentType contentType
_  Accept accept
_ V1ResourceQuota
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourcequotas"]
    KubernetesRequest
  CreateNamespacedResourceQuota contentType V1ResourceQuota accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedResourceQuota contentType V1ResourceQuota accept
-> V1ResourceQuota
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType V1ResourceQuota accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1ResourceQuota
body

data CreateNamespacedResourceQuota 
instance HasBodyParam CreateNamespacedResourceQuota V1ResourceQuota 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedResourceQuota Pretty where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> Pretty
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateNamespacedResourceQuota FieldManager where
  applyOptionalParam :: KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> FieldManager
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
applyOptionalParam KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
req KubernetesRequest
  CreateNamespacedResourceQuota contentType res accept
-> [QueryItem]
-> KubernetesRequest
     CreateNamespacedResourceQuota contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
    
-- | @*/*@
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 :: ContentType contentType
-> Accept accept
-> V1Secret
-> Namespace
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
createNamespacedSecret ContentType contentType
_  Accept accept
_ V1Secret
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/api/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/secrets"]
    KubernetesRequest
  CreateNamespacedSecret contentType V1Secret accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
    KubernetesRequest
  CreateNamespacedSecret contentType V1Secret accept
-> V1Secret
-> KubernetesRequest
     CreateNamespacedSecret contentType V1Secret accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1Secret
body

data CreateNamespacedSecret 
instance HasBodyParam CreateNamespacedSecret V1Secret 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed.
instance HasOptionalParam CreateNamespacedSecret Pretty where
  applyOptionalParam :: KubernetesRequest CreateNamespacedSecret contentType res accept
-> Pretty
-> KubernetesRequest CreateNamespacedSecret contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedSecret contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateNamespacedSecret contentType res accept
req KubernetesRequest CreateNamespacedSecret contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateNamespacedSecret contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

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

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance