{-
   Kubernetes

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

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

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

{-# 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.ResourceV1alpha2 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


-- ** ResourceV1alpha2

-- *** createNamespacedPodSchedulingContext

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts@
-- 
-- create a PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedPodSchedulingContext
  :: (Consumes CreateNamespacedPodSchedulingContext contentType, MimeRender contentType V1alpha2PodSchedulingContext)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2PodSchedulingContext -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedPodSchedulingContext contentType V1alpha2PodSchedulingContext accept
createNamespacedPodSchedulingContext :: forall contentType accept.
(Consumes CreateNamespacedPodSchedulingContext contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
ContentType contentType
-> Accept accept
-> V1alpha2PodSchedulingContext
-> Namespace
-> KubernetesRequest
     CreateNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
createNamespacedPodSchedulingContext ContentType contentType
_  Accept accept
_ V1alpha2PodSchedulingContext
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts"]
    KubernetesRequest
  CreateNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     CreateNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedPodSchedulingContext contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
KubernetesRequest
  CreateNamespacedPodSchedulingContext contentType res accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     CreateNamespacedPodSchedulingContext contentType res accept
`setBodyParam` V1alpha2PodSchedulingContext
body

data CreateNamespacedPodSchedulingContext 
instance HasBodyParam CreateNamespacedPodSchedulingContext V1alpha2PodSchedulingContext 

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

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

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

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


-- *** createNamespacedResourceClaim

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims@
-- 
-- create a ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedResourceClaim
  :: (Consumes CreateNamespacedResourceClaim contentType, MimeRender contentType V1alpha2ResourceClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaim -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedResourceClaim contentType V1alpha2ResourceClaim accept
createNamespacedResourceClaim :: forall contentType accept.
(Consumes CreateNamespacedResourceClaim contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaim
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
createNamespacedResourceClaim ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaim
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims"]
    KubernetesRequest
  CreateNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     CreateNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedResourceClaim contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
KubernetesRequest
  CreateNamespacedResourceClaim contentType res accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     CreateNamespacedResourceClaim contentType res accept
`setBodyParam` V1alpha2ResourceClaim
body

data CreateNamespacedResourceClaim 
instance HasBodyParam CreateNamespacedResourceClaim V1alpha2ResourceClaim 

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

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

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

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


-- *** createNamespacedResourceClaimParameters

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters@
-- 
-- create ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedResourceClaimParameters
  :: (Consumes CreateNamespacedResourceClaimParameters contentType, MimeRender contentType V1alpha2ResourceClaimParameters)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaimParameters -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedResourceClaimParameters contentType V1alpha2ResourceClaimParameters accept
createNamespacedResourceClaimParameters :: forall contentType accept.
(Consumes CreateNamespacedResourceClaimParameters contentType,
 MimeRender contentType V1alpha2ResourceClaimParameters) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaimParameters
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
createNamespacedResourceClaimParameters ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaimParameters
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters"]
    KubernetesRequest
  CreateNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> V1alpha2ResourceClaimParameters
-> KubernetesRequest
     CreateNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedResourceClaimParameters contentType,
 MimeRender contentType V1alpha2ResourceClaimParameters) =>
KubernetesRequest
  CreateNamespacedResourceClaimParameters contentType res accept
-> V1alpha2ResourceClaimParameters
-> KubernetesRequest
     CreateNamespacedResourceClaimParameters contentType res accept
`setBodyParam` V1alpha2ResourceClaimParameters
body

data CreateNamespacedResourceClaimParameters 
instance HasBodyParam CreateNamespacedResourceClaimParameters V1alpha2ResourceClaimParameters 

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

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

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

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


-- *** createNamespacedResourceClaimTemplate

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates@
-- 
-- create a ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedResourceClaimTemplate
  :: (Consumes CreateNamespacedResourceClaimTemplate contentType, MimeRender contentType V1alpha2ResourceClaimTemplate)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaimTemplate -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedResourceClaimTemplate contentType V1alpha2ResourceClaimTemplate accept
createNamespacedResourceClaimTemplate :: forall contentType accept.
(Consumes CreateNamespacedResourceClaimTemplate contentType,
 MimeRender contentType V1alpha2ResourceClaimTemplate) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaimTemplate
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
createNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaimTemplate
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates"]
    KubernetesRequest
  CreateNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> V1alpha2ResourceClaimTemplate
-> KubernetesRequest
     CreateNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedResourceClaimTemplate contentType,
 MimeRender contentType V1alpha2ResourceClaimTemplate) =>
KubernetesRequest
  CreateNamespacedResourceClaimTemplate contentType res accept
-> V1alpha2ResourceClaimTemplate
-> KubernetesRequest
     CreateNamespacedResourceClaimTemplate contentType res accept
`setBodyParam` V1alpha2ResourceClaimTemplate
body

data CreateNamespacedResourceClaimTemplate 
instance HasBodyParam CreateNamespacedResourceClaimTemplate V1alpha2ResourceClaimTemplate 

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

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

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

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


-- *** createNamespacedResourceClassParameters

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters@
-- 
-- create ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createNamespacedResourceClassParameters
  :: (Consumes CreateNamespacedResourceClassParameters contentType, MimeRender contentType V1alpha2ResourceClassParameters)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClassParameters -- ^ "body"
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest CreateNamespacedResourceClassParameters contentType V1alpha2ResourceClassParameters accept
createNamespacedResourceClassParameters :: forall contentType accept.
(Consumes CreateNamespacedResourceClassParameters contentType,
 MimeRender contentType V1alpha2ResourceClassParameters) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClassParameters
-> Namespace
-> KubernetesRequest
     CreateNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
createNamespacedResourceClassParameters ContentType contentType
_  Accept accept
_ V1alpha2ResourceClassParameters
body (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters"]
    KubernetesRequest
  CreateNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> V1alpha2ResourceClassParameters
-> KubernetesRequest
     CreateNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateNamespacedResourceClassParameters contentType,
 MimeRender contentType V1alpha2ResourceClassParameters) =>
KubernetesRequest
  CreateNamespacedResourceClassParameters contentType res accept
-> V1alpha2ResourceClassParameters
-> KubernetesRequest
     CreateNamespacedResourceClassParameters contentType res accept
`setBodyParam` V1alpha2ResourceClassParameters
body

data CreateNamespacedResourceClassParameters 
instance HasBodyParam CreateNamespacedResourceClassParameters V1alpha2ResourceClassParameters 

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

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

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

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


-- *** createResourceClass

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses@
-- 
-- create a ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createResourceClass
  :: (Consumes CreateResourceClass contentType, MimeRender contentType V1alpha2ResourceClass)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClass -- ^ "body"
  -> KubernetesRequest CreateResourceClass contentType V1alpha2ResourceClass accept
createResourceClass :: forall contentType accept.
(Consumes CreateResourceClass contentType,
 MimeRender contentType V1alpha2ResourceClass) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClass
-> KubernetesRequest
     CreateResourceClass contentType V1alpha2ResourceClass accept
createResourceClass ContentType contentType
_  Accept accept
_ V1alpha2ResourceClass
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateResourceClass contentType V1alpha2ResourceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses"]
    KubernetesRequest
  CreateResourceClass contentType V1alpha2ResourceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateResourceClass contentType V1alpha2ResourceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateResourceClass contentType V1alpha2ResourceClass accept
-> V1alpha2ResourceClass
-> KubernetesRequest
     CreateResourceClass contentType V1alpha2ResourceClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateResourceClass contentType,
 MimeRender contentType V1alpha2ResourceClass) =>
KubernetesRequest CreateResourceClass contentType res accept
-> V1alpha2ResourceClass
-> KubernetesRequest CreateResourceClass contentType res accept
`setBodyParam` V1alpha2ResourceClass
body

data CreateResourceClass 
instance HasBodyParam CreateResourceClass V1alpha2ResourceClass 

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

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

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

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


-- *** createResourceSlice

-- | @POST \/apis\/resource.k8s.io\/v1alpha2\/resourceslices@
-- 
-- create a ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createResourceSlice
  :: (Consumes CreateResourceSlice contentType, MimeRender contentType V1alpha2ResourceSlice)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceSlice -- ^ "body"
  -> KubernetesRequest CreateResourceSlice contentType V1alpha2ResourceSlice accept
createResourceSlice :: forall contentType accept.
(Consumes CreateResourceSlice contentType,
 MimeRender contentType V1alpha2ResourceSlice) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceSlice
-> KubernetesRequest
     CreateResourceSlice contentType V1alpha2ResourceSlice accept
createResourceSlice ContentType contentType
_  Accept accept
_ V1alpha2ResourceSlice
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateResourceSlice contentType V1alpha2ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices"]
    KubernetesRequest
  CreateResourceSlice contentType V1alpha2ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateResourceSlice contentType V1alpha2ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateResourceSlice contentType V1alpha2ResourceSlice accept
-> V1alpha2ResourceSlice
-> KubernetesRequest
     CreateResourceSlice contentType V1alpha2ResourceSlice accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes CreateResourceSlice contentType,
 MimeRender contentType V1alpha2ResourceSlice) =>
KubernetesRequest CreateResourceSlice contentType res accept
-> V1alpha2ResourceSlice
-> KubernetesRequest CreateResourceSlice contentType res accept
`setBodyParam` V1alpha2ResourceSlice
body

data CreateResourceSlice 
instance HasBodyParam CreateResourceSlice V1alpha2ResourceSlice 

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

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

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

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


-- *** deleteCollectionNamespacedPodSchedulingContext

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

data DeleteCollectionNamespacedPodSchedulingContext 
instance HasBodyParam DeleteCollectionNamespacedPodSchedulingContext V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionNamespacedResourceClaim

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

data DeleteCollectionNamespacedResourceClaim 
instance HasBodyParam DeleteCollectionNamespacedResourceClaim V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionNamespacedResourceClaimParameters

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

data DeleteCollectionNamespacedResourceClaimParameters 
instance HasBodyParam DeleteCollectionNamespacedResourceClaimParameters V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionNamespacedResourceClaimTemplate

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

data DeleteCollectionNamespacedResourceClaimTemplate 
instance HasBodyParam DeleteCollectionNamespacedResourceClaimTemplate V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionNamespacedResourceClassParameters

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

data DeleteCollectionNamespacedResourceClassParameters 
instance HasBodyParam DeleteCollectionNamespacedResourceClassParameters V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionResourceClass

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses@
-- 
-- delete collection of ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionResourceClass
  :: (Consumes DeleteCollectionResourceClass contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionResourceClass contentType V1Status accept
deleteCollectionResourceClass :: forall contentType accept.
Consumes DeleteCollectionResourceClass contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionResourceClass contentType V1Status accept
deleteCollectionResourceClass ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionResourceClass contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses"]
    KubernetesRequest
  DeleteCollectionResourceClass contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionResourceClass contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionResourceClass 
instance HasBodyParam DeleteCollectionResourceClass V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteCollectionResourceSlice

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/resourceslices@
-- 
-- delete collection of ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionResourceSlice
  :: (Consumes DeleteCollectionResourceSlice contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionResourceSlice contentType V1Status accept
deleteCollectionResourceSlice :: forall contentType accept.
Consumes DeleteCollectionResourceSlice contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionResourceSlice contentType V1Status accept
deleteCollectionResourceSlice ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionResourceSlice contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices"]
    KubernetesRequest
  DeleteCollectionResourceSlice contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionResourceSlice contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionResourceSlice 
instance HasBodyParam DeleteCollectionResourceSlice V1DeleteOptions 

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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


-- *** deleteNamespacedPodSchedulingContext

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}@
-- 
-- delete a PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedPodSchedulingContext
  :: (Consumes DeleteNamespacedPodSchedulingContext contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedPodSchedulingContext contentType V1alpha2PodSchedulingContext accept
deleteNamespacedPodSchedulingContext :: forall contentType accept.
Consumes DeleteNamespacedPodSchedulingContext contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
deleteNamespacedPodSchedulingContext ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteNamespacedPodSchedulingContext 
instance HasBodyParam DeleteNamespacedPodSchedulingContext V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteNamespacedResourceClaim

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}@
-- 
-- delete a ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedResourceClaim
  :: (Consumes DeleteNamespacedResourceClaim contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedResourceClaim contentType V1alpha2ResourceClaim accept
deleteNamespacedResourceClaim :: forall contentType accept.
Consumes DeleteNamespacedResourceClaim contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
deleteNamespacedResourceClaim ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteNamespacedResourceClaim 
instance HasBodyParam DeleteNamespacedResourceClaim V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteNamespacedResourceClaimParameters

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters\/{name}@
-- 
-- delete ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedResourceClaimParameters
  :: (Consumes DeleteNamespacedResourceClaimParameters contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaimParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedResourceClaimParameters contentType V1alpha2ResourceClaimParameters accept
deleteNamespacedResourceClaimParameters :: forall contentType accept.
Consumes DeleteNamespacedResourceClaimParameters contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
deleteNamespacedResourceClaimParameters ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteNamespacedResourceClaimParameters 
instance HasBodyParam DeleteNamespacedResourceClaimParameters V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteNamespacedResourceClaimTemplate

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates\/{name}@
-- 
-- delete a ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedResourceClaimTemplate
  :: (Consumes DeleteNamespacedResourceClaimTemplate contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaimTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedResourceClaimTemplate contentType V1alpha2ResourceClaimTemplate accept
deleteNamespacedResourceClaimTemplate :: forall contentType accept.
Consumes DeleteNamespacedResourceClaimTemplate contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
deleteNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteNamespacedResourceClaimTemplate 
instance HasBodyParam DeleteNamespacedResourceClaimTemplate V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteNamespacedResourceClassParameters

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters\/{name}@
-- 
-- delete ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteNamespacedResourceClassParameters
  :: (Consumes DeleteNamespacedResourceClassParameters contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClassParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest DeleteNamespacedResourceClassParameters contentType V1alpha2ResourceClassParameters accept
deleteNamespacedResourceClassParameters :: forall contentType accept.
Consumes DeleteNamespacedResourceClassParameters contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
deleteNamespacedResourceClassParameters ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteNamespacedResourceClassParameters 
instance HasBodyParam DeleteNamespacedResourceClassParameters V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteResourceClass

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses\/{name}@
-- 
-- delete a ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteResourceClass
  :: (Consumes DeleteResourceClass contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClass
  -> KubernetesRequest DeleteResourceClass contentType V1alpha2ResourceClass accept
deleteResourceClass :: forall contentType accept.
Consumes DeleteResourceClass contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeleteResourceClass contentType V1alpha2ResourceClass accept
deleteResourceClass ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteResourceClass contentType V1alpha2ResourceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteResourceClass contentType V1alpha2ResourceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteResourceClass contentType V1alpha2ResourceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteResourceClass 
instance HasBodyParam DeleteResourceClass V1DeleteOptions 

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

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

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

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

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

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


-- *** deleteResourceSlice

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha2\/resourceslices\/{name}@
-- 
-- delete a ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteResourceSlice
  :: (Consumes DeleteResourceSlice contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceSlice
  -> KubernetesRequest DeleteResourceSlice contentType V1alpha2ResourceSlice accept
deleteResourceSlice :: forall contentType accept.
Consumes DeleteResourceSlice contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha2ResourceSlice accept
deleteResourceSlice ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha2ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteResourceSlice contentType V1alpha2ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha2ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteResourceSlice 
instance HasBodyParam DeleteResourceSlice V1DeleteOptions 

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

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

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

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

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

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


-- *** getAPIResources

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

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


-- *** listNamespacedPodSchedulingContext

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts@
-- 
-- list or watch objects of kind PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedPodSchedulingContext
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedPodSchedulingContext MimeNoContent V1alpha2PodSchedulingContextList accept
listNamespacedPodSchedulingContext :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
listNamespacedPodSchedulingContext  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts"]
    KubernetesRequest
  ListNamespacedPodSchedulingContext
  MimeNoContent
  V1alpha2PodSchedulingContextList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListNamespacedPodSchedulingContext  

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

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

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

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

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

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

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

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

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

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

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


-- *** listNamespacedResourceClaim

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims@
-- 
-- list or watch objects of kind ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedResourceClaim
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedResourceClaim MimeNoContent V1alpha2ResourceClaimList accept
listNamespacedResourceClaim :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
listNamespacedResourceClaim  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims"]
    KubernetesRequest
  ListNamespacedResourceClaim
  MimeNoContent
  V1alpha2ResourceClaimList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListNamespacedResourceClaim  

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

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

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

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

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

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

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

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

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

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

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


-- *** listNamespacedResourceClaimParameters

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters@
-- 
-- list or watch objects of kind ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedResourceClaimParameters
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedResourceClaimParameters MimeNoContent V1alpha2ResourceClaimParametersList accept
listNamespacedResourceClaimParameters :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
listNamespacedResourceClaimParameters  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters"]
    KubernetesRequest
  ListNamespacedResourceClaimParameters
  MimeNoContent
  V1alpha2ResourceClaimParametersList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListNamespacedResourceClaimParameters  

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

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

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

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

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

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

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

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

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

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

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


-- *** listNamespacedResourceClaimTemplate

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates@
-- 
-- list or watch objects of kind ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedResourceClaimTemplate
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedResourceClaimTemplate MimeNoContent V1alpha2ResourceClaimTemplateList accept
listNamespacedResourceClaimTemplate :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
listNamespacedResourceClaimTemplate  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates"]
    KubernetesRequest
  ListNamespacedResourceClaimTemplate
  MimeNoContent
  V1alpha2ResourceClaimTemplateList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListNamespacedResourceClaimTemplate  

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

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

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

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

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

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

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

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

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

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

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


-- *** listNamespacedResourceClassParameters

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters@
-- 
-- list or watch objects of kind ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listNamespacedResourceClassParameters
  :: Accept accept -- ^ request accept ('MimeType')
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ListNamespacedResourceClassParameters MimeNoContent V1alpha2ResourceClassParametersList accept
listNamespacedResourceClassParameters :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
listNamespacedResourceClassParameters  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters"]
    KubernetesRequest
  ListNamespacedResourceClassParameters
  MimeNoContent
  V1alpha2ResourceClassParametersList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListNamespacedResourceClassParameters  

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

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

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

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

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

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

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

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

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

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

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


-- *** listPodSchedulingContextForAllNamespaces

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/podschedulingcontexts@
-- 
-- list or watch objects of kind PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPodSchedulingContextForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPodSchedulingContextForAllNamespaces MimeNoContent V1alpha2PodSchedulingContextList accept
listPodSchedulingContextForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListPodSchedulingContextForAllNamespaces
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
listPodSchedulingContextForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPodSchedulingContextForAllNamespaces
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/podschedulingcontexts"]
    KubernetesRequest
  ListPodSchedulingContextForAllNamespaces
  MimeNoContent
  V1alpha2PodSchedulingContextList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPodSchedulingContextForAllNamespaces
     MimeNoContent
     V1alpha2PodSchedulingContextList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListPodSchedulingContextForAllNamespaces  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceClaimForAllNamespaces

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclaims@
-- 
-- list or watch objects of kind ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceClaimForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceClaimForAllNamespaces MimeNoContent V1alpha2ResourceClaimList accept
listResourceClaimForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceClaimForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
listResourceClaimForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceClaimForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclaims"]
    KubernetesRequest
  ListResourceClaimForAllNamespaces
  MimeNoContent
  V1alpha2ResourceClaimList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceClaimForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceClaimForAllNamespaces  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceClaimParametersForAllNamespaces

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclaimparameters@
-- 
-- list or watch objects of kind ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceClaimParametersForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceClaimParametersForAllNamespaces MimeNoContent V1alpha2ResourceClaimParametersList accept
listResourceClaimParametersForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceClaimParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
listResourceClaimParametersForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceClaimParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclaimparameters"]
    KubernetesRequest
  ListResourceClaimParametersForAllNamespaces
  MimeNoContent
  V1alpha2ResourceClaimParametersList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceClaimParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimParametersList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceClaimParametersForAllNamespaces  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceClaimTemplateForAllNamespaces

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclaimtemplates@
-- 
-- list or watch objects of kind ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceClaimTemplateForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceClaimTemplateForAllNamespaces MimeNoContent V1alpha2ResourceClaimTemplateList accept
listResourceClaimTemplateForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceClaimTemplateForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
listResourceClaimTemplateForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceClaimTemplateForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclaimtemplates"]
    KubernetesRequest
  ListResourceClaimTemplateForAllNamespaces
  MimeNoContent
  V1alpha2ResourceClaimTemplateList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceClaimTemplateForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClaimTemplateList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceClaimTemplateForAllNamespaces  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceClass

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses@
-- 
-- list or watch objects of kind ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceClass
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceClass MimeNoContent V1alpha2ResourceClassList accept
listResourceClass :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceClass MimeNoContent V1alpha2ResourceClassList accept
listResourceClass  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceClass MimeNoContent V1alpha2ResourceClassList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses"]
    KubernetesRequest
  ListResourceClass MimeNoContent V1alpha2ResourceClassList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceClass MimeNoContent V1alpha2ResourceClassList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceClass  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceClassParametersForAllNamespaces

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclassparameters@
-- 
-- list or watch objects of kind ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceClassParametersForAllNamespaces
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceClassParametersForAllNamespaces MimeNoContent V1alpha2ResourceClassParametersList accept
listResourceClassParametersForAllNamespaces :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceClassParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
listResourceClassParametersForAllNamespaces  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceClassParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclassparameters"]
    KubernetesRequest
  ListResourceClassParametersForAllNamespaces
  MimeNoContent
  V1alpha2ResourceClassParametersList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceClassParametersForAllNamespaces
     MimeNoContent
     V1alpha2ResourceClassParametersList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceClassParametersForAllNamespaces  

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

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

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

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

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

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

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

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

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

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

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


-- *** listResourceSlice

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceslices@
-- 
-- list or watch objects of kind ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listResourceSlice
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListResourceSlice MimeNoContent V1alpha2ResourceSliceList accept
listResourceSlice :: forall accept.
Accept accept
-> KubernetesRequest
     ListResourceSlice MimeNoContent V1alpha2ResourceSliceList accept
listResourceSlice  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListResourceSlice MimeNoContent V1alpha2ResourceSliceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices"]
    KubernetesRequest
  ListResourceSlice MimeNoContent V1alpha2ResourceSliceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListResourceSlice MimeNoContent V1alpha2ResourceSliceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ListResourceSlice  

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

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

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

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

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

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

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

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

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

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

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


-- *** patchNamespacedPodSchedulingContext

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}@
-- 
-- partially update the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodSchedulingContext
  :: (Consumes PatchNamespacedPodSchedulingContext contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodSchedulingContext contentType V1alpha2PodSchedulingContext accept
patchNamespacedPodSchedulingContext :: forall contentType accept.
(Consumes PatchNamespacedPodSchedulingContext contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
patchNamespacedPodSchedulingContext ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodSchedulingContext contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedPodSchedulingContext contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodSchedulingContext 
instance HasBodyParam PatchNamespacedPodSchedulingContext Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodSchedulingContext Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodSchedulingContext contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodSchedulingContext contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedPodSchedulingContext contentType res accept
req KubernetesRequest
  PatchNamespacedPodSchedulingContext contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodSchedulingContext contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodSchedulingContext MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodSchedulingContext MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodSchedulingContext MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodSchedulingContext MimeStrategicMergePatchjson

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


-- *** patchNamespacedPodSchedulingContextStatus

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}\/status@
-- 
-- partially update status of the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedPodSchedulingContextStatus
  :: (Consumes PatchNamespacedPodSchedulingContextStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedPodSchedulingContextStatus contentType V1alpha2PodSchedulingContext accept
patchNamespacedPodSchedulingContextStatus :: forall contentType accept.
(Consumes PatchNamespacedPodSchedulingContextStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
patchNamespacedPodSchedulingContextStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedPodSchedulingContextStatus
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedPodSchedulingContextStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedPodSchedulingContextStatus 
instance HasBodyParam PatchNamespacedPodSchedulingContextStatus Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedPodSchedulingContextStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus contentType res accept
req KubernetesRequest
  PatchNamespacedPodSchedulingContextStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedPodSchedulingContextStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedPodSchedulingContextStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedPodSchedulingContextStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedPodSchedulingContextStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedPodSchedulingContextStatus MimeStrategicMergePatchjson

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


-- *** patchNamespacedResourceClaim

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}@
-- 
-- partially update the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceClaim
  :: (Consumes PatchNamespacedResourceClaim contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceClaim contentType V1alpha2ResourceClaim accept
patchNamespacedResourceClaim :: forall contentType accept.
(Consumes PatchNamespacedResourceClaim contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
patchNamespacedResourceClaim ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceClaim contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceClaim contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaim contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceClaim 
instance HasBodyParam PatchNamespacedResourceClaim Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceClaim Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceClaim contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceClaim contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceClaim contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceClaim contentType res accept
req KubernetesRequest
  PatchNamespacedResourceClaim contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceClaim contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceClaim MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceClaim MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceClaim MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceClaim MimeStrategicMergePatchjson

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


-- *** patchNamespacedResourceClaimParameters

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters\/{name}@
-- 
-- partially update the specified ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceClaimParameters
  :: (Consumes PatchNamespacedResourceClaimParameters contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaimParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceClaimParameters contentType V1alpha2ResourceClaimParameters accept
patchNamespacedResourceClaimParameters :: forall contentType accept.
(Consumes PatchNamespacedResourceClaimParameters contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
patchNamespacedResourceClaimParameters ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceClaimParameters contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceClaimParameters contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceClaimParameters 
instance HasBodyParam PatchNamespacedResourceClaimParameters Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceClaimParameters Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceClaimParameters contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceClaimParameters contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceClaimParameters contentType res accept
req KubernetesRequest
  PatchNamespacedResourceClaimParameters contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceClaimParameters contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceClaimParameters MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceClaimParameters MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceClaimParameters MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceClaimParameters MimeStrategicMergePatchjson

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


-- *** patchNamespacedResourceClaimStatus

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}\/status@
-- 
-- partially update status of the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceClaimStatus
  :: (Consumes PatchNamespacedResourceClaimStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceClaimStatus contentType V1alpha2ResourceClaim accept
patchNamespacedResourceClaimStatus :: forall contentType accept.
(Consumes PatchNamespacedResourceClaimStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
patchNamespacedResourceClaimStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchNamespacedResourceClaimStatus
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedResourceClaimStatus
  contentType
  V1alpha2ResourceClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceClaimStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceClaimStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceClaimStatus 
instance HasBodyParam PatchNamespacedResourceClaimStatus Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceClaimStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceClaimStatus contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceClaimStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceClaimStatus contentType res accept
req KubernetesRequest
  PatchNamespacedResourceClaimStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceClaimStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceClaimStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceClaimStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceClaimStatus MimeStrategicMergePatchjson

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


-- *** patchNamespacedResourceClaimTemplate

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates\/{name}@
-- 
-- partially update the specified ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceClaimTemplate
  :: (Consumes PatchNamespacedResourceClaimTemplate contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaimTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceClaimTemplate contentType V1alpha2ResourceClaimTemplate accept
patchNamespacedResourceClaimTemplate :: forall contentType accept.
(Consumes PatchNamespacedResourceClaimTemplate contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
patchNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceClaimTemplate contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceClaimTemplate contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceClaimTemplate 
instance HasBodyParam PatchNamespacedResourceClaimTemplate Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceClaimTemplate Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceClaimTemplate contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceClaimTemplate contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceClaimTemplate contentType res accept
req KubernetesRequest
  PatchNamespacedResourceClaimTemplate contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceClaimTemplate MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceClaimTemplate MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceClaimTemplate MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceClaimTemplate MimeStrategicMergePatchjson

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


-- *** patchNamespacedResourceClassParameters

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters\/{name}@
-- 
-- partially update the specified ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchNamespacedResourceClassParameters
  :: (Consumes PatchNamespacedResourceClassParameters contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClassParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest PatchNamespacedResourceClassParameters contentType V1alpha2ResourceClassParameters accept
patchNamespacedResourceClassParameters :: forall contentType accept.
(Consumes PatchNamespacedResourceClassParameters contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
patchNamespacedResourceClassParameters ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchNamespacedResourceClassParameters contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchNamespacedResourceClassParameters contentType res accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClassParameters contentType res accept
`setBodyParam` Body
body

data PatchNamespacedResourceClassParameters 
instance HasBodyParam PatchNamespacedResourceClassParameters Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchNamespacedResourceClassParameters Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  PatchNamespacedResourceClassParameters contentType res accept
-> Force
-> KubernetesRequest
     PatchNamespacedResourceClassParameters contentType res accept
applyOptionalParam KubernetesRequest
  PatchNamespacedResourceClassParameters contentType res accept
req (Force Bool
xs) =
    KubernetesRequest
  PatchNamespacedResourceClassParameters contentType res accept
req KubernetesRequest
  PatchNamespacedResourceClassParameters contentType res accept
-> [QueryItem]
-> KubernetesRequest
     PatchNamespacedResourceClassParameters contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchNamespacedResourceClassParameters MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchNamespacedResourceClassParameters MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchNamespacedResourceClassParameters MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchNamespacedResourceClassParameters MimeStrategicMergePatchjson

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


-- *** patchResourceClass

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses\/{name}@
-- 
-- partially update the specified ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchResourceClass
  :: (Consumes PatchResourceClass contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClass
  -> KubernetesRequest PatchResourceClass contentType V1alpha2ResourceClass accept
patchResourceClass :: forall contentType accept.
(Consumes PatchResourceClass contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchResourceClass contentType V1alpha2ResourceClass accept
patchResourceClass ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchResourceClass contentType V1alpha2ResourceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchResourceClass contentType V1alpha2ResourceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchResourceClass contentType V1alpha2ResourceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchResourceClass contentType V1alpha2ResourceClass accept
-> Body
-> KubernetesRequest
     PatchResourceClass contentType V1alpha2ResourceClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchResourceClass contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchResourceClass contentType res accept
-> Body
-> KubernetesRequest PatchResourceClass contentType res accept
`setBodyParam` Body
body

data PatchResourceClass 
instance HasBodyParam PatchResourceClass Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchResourceClass Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchResourceClass contentType res accept
-> Force
-> KubernetesRequest PatchResourceClass contentType res accept
applyOptionalParam KubernetesRequest PatchResourceClass contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchResourceClass contentType res accept
req KubernetesRequest PatchResourceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchResourceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchResourceClass MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchResourceClass MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchResourceClass MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchResourceClass MimeStrategicMergePatchjson

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


-- *** patchResourceSlice

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha2\/resourceslices\/{name}@
-- 
-- partially update the specified ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchResourceSlice
  :: (Consumes PatchResourceSlice contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceSlice
  -> KubernetesRequest PatchResourceSlice contentType V1alpha2ResourceSlice accept
patchResourceSlice :: forall contentType accept.
(Consumes PatchResourceSlice contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha2ResourceSlice accept
patchResourceSlice ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha2ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchResourceSlice contentType V1alpha2ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha2ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  PatchResourceSlice contentType V1alpha2ResourceSlice accept
-> Body
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha2ResourceSlice accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes PatchResourceSlice contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchResourceSlice contentType res accept
-> Body
-> KubernetesRequest PatchResourceSlice contentType res accept
`setBodyParam` Body
body

data PatchResourceSlice 
instance HasBodyParam PatchResourceSlice Body 

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

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

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

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchResourceSlice Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchResourceSlice contentType res accept
-> Force
-> KubernetesRequest PatchResourceSlice contentType res accept
applyOptionalParam KubernetesRequest PatchResourceSlice contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchResourceSlice contentType res accept
req KubernetesRequest PatchResourceSlice contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchResourceSlice contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | @application/apply-patch+yaml@
instance Consumes PatchResourceSlice MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchResourceSlice MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchResourceSlice MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchResourceSlice MimeStrategicMergePatchjson

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


-- *** readNamespacedPodSchedulingContext

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}@
-- 
-- read the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodSchedulingContext
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodSchedulingContext MimeNoContent V1alpha2PodSchedulingContext accept
readNamespacedPodSchedulingContext :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
readNamespacedPodSchedulingContext  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedPodSchedulingContext
  MimeNoContent
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodSchedulingContext
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedPodSchedulingContext  

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


-- *** readNamespacedPodSchedulingContextStatus

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}\/status@
-- 
-- read status of the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedPodSchedulingContextStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedPodSchedulingContextStatus MimeNoContent V1alpha2PodSchedulingContext accept
readNamespacedPodSchedulingContextStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedPodSchedulingContextStatus
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
readNamespacedPodSchedulingContextStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedPodSchedulingContextStatus
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedPodSchedulingContextStatus
  MimeNoContent
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedPodSchedulingContextStatus
     MimeNoContent
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedPodSchedulingContextStatus  

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


-- *** readNamespacedResourceClaim

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}@
-- 
-- read the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceClaim
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceClaim MimeNoContent V1alpha2ResourceClaim accept
readNamespacedResourceClaim :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaim
     accept
readNamespacedResourceClaim  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedResourceClaim
  MimeNoContent
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedResourceClaim  

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


-- *** readNamespacedResourceClaimParameters

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters\/{name}@
-- 
-- read the specified ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceClaimParameters
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaimParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceClaimParameters MimeNoContent V1alpha2ResourceClaimParameters accept
readNamespacedResourceClaimParameters :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParameters
     accept
readNamespacedResourceClaimParameters  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedResourceClaimParameters
  MimeNoContent
  V1alpha2ResourceClaimParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaimParameters
     MimeNoContent
     V1alpha2ResourceClaimParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedResourceClaimParameters  

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


-- *** readNamespacedResourceClaimStatus

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}\/status@
-- 
-- read status of the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceClaimStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceClaimStatus MimeNoContent V1alpha2ResourceClaim accept
readNamespacedResourceClaimStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha2ResourceClaim
     accept
readNamespacedResourceClaimStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadNamespacedResourceClaimStatus
  MimeNoContent
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedResourceClaimStatus  

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


-- *** readNamespacedResourceClaimTemplate

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates\/{name}@
-- 
-- read the specified ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceClaimTemplate
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClaimTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceClaimTemplate MimeNoContent V1alpha2ResourceClaimTemplate accept
readNamespacedResourceClaimTemplate :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplate
     accept
readNamespacedResourceClaimTemplate  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedResourceClaimTemplate
  MimeNoContent
  V1alpha2ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha2ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedResourceClaimTemplate  

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


-- *** readNamespacedResourceClassParameters

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters\/{name}@
-- 
-- read the specified ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readNamespacedResourceClassParameters
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClassParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReadNamespacedResourceClassParameters MimeNoContent V1alpha2ResourceClassParameters accept
readNamespacedResourceClassParameters :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParameters
     accept
readNamespacedResourceClassParameters  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadNamespacedResourceClassParameters
  MimeNoContent
  V1alpha2ResourceClassParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClassParameters
     MimeNoContent
     V1alpha2ResourceClassParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadNamespacedResourceClassParameters  

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


-- *** readResourceClass

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses\/{name}@
-- 
-- read the specified ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readResourceClass
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceClass
  -> KubernetesRequest ReadResourceClass MimeNoContent V1alpha2ResourceClass accept
readResourceClass :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadResourceClass MimeNoContent V1alpha2ResourceClass accept
readResourceClass  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadResourceClass MimeNoContent V1alpha2ResourceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadResourceClass MimeNoContent V1alpha2ResourceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadResourceClass MimeNoContent V1alpha2ResourceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadResourceClass  

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


-- *** readResourceSlice

-- | @GET \/apis\/resource.k8s.io\/v1alpha2\/resourceslices\/{name}@
-- 
-- read the specified ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readResourceSlice
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ResourceSlice
  -> KubernetesRequest ReadResourceSlice MimeNoContent V1alpha2ResourceSlice accept
readResourceSlice :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadResourceSlice MimeNoContent V1alpha2ResourceSlice accept
readResourceSlice  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadResourceSlice MimeNoContent V1alpha2ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadResourceSlice MimeNoContent V1alpha2ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadResourceSlice MimeNoContent V1alpha2ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 ReadResourceSlice  

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


-- *** replaceNamespacedPodSchedulingContext

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}@
-- 
-- replace the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodSchedulingContext
  :: (Consumes ReplaceNamespacedPodSchedulingContext contentType, MimeRender contentType V1alpha2PodSchedulingContext)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2PodSchedulingContext -- ^ "body"
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodSchedulingContext contentType V1alpha2PodSchedulingContext accept
replaceNamespacedPodSchedulingContext :: forall contentType accept.
(Consumes ReplaceNamespacedPodSchedulingContext contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
ContentType contentType
-> Accept accept
-> V1alpha2PodSchedulingContext
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
replaceNamespacedPodSchedulingContext ContentType contentType
_  Accept accept
_ V1alpha2PodSchedulingContext
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedPodSchedulingContext
  contentType
  V1alpha2PodSchedulingContext
  accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContext
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodSchedulingContext contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
KubernetesRequest
  ReplaceNamespacedPodSchedulingContext contentType res accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContext contentType res accept
`setBodyParam` V1alpha2PodSchedulingContext
body

data ReplaceNamespacedPodSchedulingContext 
instance HasBodyParam ReplaceNamespacedPodSchedulingContext V1alpha2PodSchedulingContext 

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

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

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

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


-- *** replaceNamespacedPodSchedulingContextStatus

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/podschedulingcontexts\/{name}\/status@
-- 
-- replace status of the specified PodSchedulingContext
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedPodSchedulingContextStatus
  :: (Consumes ReplaceNamespacedPodSchedulingContextStatus contentType, MimeRender contentType V1alpha2PodSchedulingContext)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2PodSchedulingContext -- ^ "body"
  -> Name -- ^ "name" -  name of the PodSchedulingContext
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedPodSchedulingContextStatus contentType V1alpha2PodSchedulingContext accept
replaceNamespacedPodSchedulingContextStatus :: forall contentType accept.
(Consumes ReplaceNamespacedPodSchedulingContextStatus contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
ContentType contentType
-> Accept accept
-> V1alpha2PodSchedulingContext
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
replaceNamespacedPodSchedulingContextStatus ContentType contentType
_  Accept accept
_ V1alpha2PodSchedulingContext
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/podschedulingcontexts/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedPodSchedulingContextStatus
  contentType
  V1alpha2PodSchedulingContext
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedPodSchedulingContextStatus
  contentType
  V1alpha2PodSchedulingContext
  accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContextStatus
     contentType
     V1alpha2PodSchedulingContext
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedPodSchedulingContextStatus contentType,
 MimeRender contentType V1alpha2PodSchedulingContext) =>
KubernetesRequest
  ReplaceNamespacedPodSchedulingContextStatus contentType res accept
-> V1alpha2PodSchedulingContext
-> KubernetesRequest
     ReplaceNamespacedPodSchedulingContextStatus contentType res accept
`setBodyParam` V1alpha2PodSchedulingContext
body

data ReplaceNamespacedPodSchedulingContextStatus 
instance HasBodyParam ReplaceNamespacedPodSchedulingContextStatus V1alpha2PodSchedulingContext 

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

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

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

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


-- *** replaceNamespacedResourceClaim

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}@
-- 
-- replace the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceClaim
  :: (Consumes ReplaceNamespacedResourceClaim contentType, MimeRender contentType V1alpha2ResourceClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaim -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceClaim contentType V1alpha2ResourceClaim accept
replaceNamespacedResourceClaim :: forall contentType accept.
(Consumes ReplaceNamespacedResourceClaim contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaim
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
replaceNamespacedResourceClaim ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaim
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedResourceClaim
  contentType
  V1alpha2ResourceClaim
  accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     ReplaceNamespacedResourceClaim
     contentType
     V1alpha2ResourceClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceClaim contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
KubernetesRequest
  ReplaceNamespacedResourceClaim contentType res accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     ReplaceNamespacedResourceClaim contentType res accept
`setBodyParam` V1alpha2ResourceClaim
body

data ReplaceNamespacedResourceClaim 
instance HasBodyParam ReplaceNamespacedResourceClaim V1alpha2ResourceClaim 

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

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

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

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


-- *** replaceNamespacedResourceClaimParameters

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimparameters\/{name}@
-- 
-- replace the specified ResourceClaimParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceClaimParameters
  :: (Consumes ReplaceNamespacedResourceClaimParameters contentType, MimeRender contentType V1alpha2ResourceClaimParameters)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaimParameters -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaimParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceClaimParameters contentType V1alpha2ResourceClaimParameters accept
replaceNamespacedResourceClaimParameters :: forall contentType accept.
(Consumes ReplaceNamespacedResourceClaimParameters contentType,
 MimeRender contentType V1alpha2ResourceClaimParameters) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaimParameters
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
replaceNamespacedResourceClaimParameters ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaimParameters
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedResourceClaimParameters
  contentType
  V1alpha2ResourceClaimParameters
  accept
-> V1alpha2ResourceClaimParameters
-> KubernetesRequest
     ReplaceNamespacedResourceClaimParameters
     contentType
     V1alpha2ResourceClaimParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceClaimParameters contentType,
 MimeRender contentType V1alpha2ResourceClaimParameters) =>
KubernetesRequest
  ReplaceNamespacedResourceClaimParameters contentType res accept
-> V1alpha2ResourceClaimParameters
-> KubernetesRequest
     ReplaceNamespacedResourceClaimParameters contentType res accept
`setBodyParam` V1alpha2ResourceClaimParameters
body

data ReplaceNamespacedResourceClaimParameters 
instance HasBodyParam ReplaceNamespacedResourceClaimParameters V1alpha2ResourceClaimParameters 

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

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

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

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


-- *** replaceNamespacedResourceClaimStatus

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaims\/{name}\/status@
-- 
-- replace status of the specified ResourceClaim
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceClaimStatus
  :: (Consumes ReplaceNamespacedResourceClaimStatus contentType, MimeRender contentType V1alpha2ResourceClaim)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaim -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaim
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceClaimStatus contentType V1alpha2ResourceClaim accept
replaceNamespacedResourceClaimStatus :: forall contentType accept.
(Consumes ReplaceNamespacedResourceClaimStatus contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaim
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
replaceNamespacedResourceClaimStatus ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaim
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceNamespacedResourceClaimStatus
  contentType
  V1alpha2ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedResourceClaimStatus
  contentType
  V1alpha2ResourceClaim
  accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     ReplaceNamespacedResourceClaimStatus
     contentType
     V1alpha2ResourceClaim
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceClaimStatus contentType,
 MimeRender contentType V1alpha2ResourceClaim) =>
KubernetesRequest
  ReplaceNamespacedResourceClaimStatus contentType res accept
-> V1alpha2ResourceClaim
-> KubernetesRequest
     ReplaceNamespacedResourceClaimStatus contentType res accept
`setBodyParam` V1alpha2ResourceClaim
body

data ReplaceNamespacedResourceClaimStatus 
instance HasBodyParam ReplaceNamespacedResourceClaimStatus V1alpha2ResourceClaim 

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

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

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

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


-- *** replaceNamespacedResourceClaimTemplate

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclaimtemplates\/{name}@
-- 
-- replace the specified ResourceClaimTemplate
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceClaimTemplate
  :: (Consumes ReplaceNamespacedResourceClaimTemplate contentType, MimeRender contentType V1alpha2ResourceClaimTemplate)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClaimTemplate -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClaimTemplate
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceClaimTemplate contentType V1alpha2ResourceClaimTemplate accept
replaceNamespacedResourceClaimTemplate :: forall contentType accept.
(Consumes ReplaceNamespacedResourceClaimTemplate contentType,
 MimeRender contentType V1alpha2ResourceClaimTemplate) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClaimTemplate
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
replaceNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ V1alpha2ResourceClaimTemplate
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedResourceClaimTemplate
  contentType
  V1alpha2ResourceClaimTemplate
  accept
-> V1alpha2ResourceClaimTemplate
-> KubernetesRequest
     ReplaceNamespacedResourceClaimTemplate
     contentType
     V1alpha2ResourceClaimTemplate
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceClaimTemplate contentType,
 MimeRender contentType V1alpha2ResourceClaimTemplate) =>
KubernetesRequest
  ReplaceNamespacedResourceClaimTemplate contentType res accept
-> V1alpha2ResourceClaimTemplate
-> KubernetesRequest
     ReplaceNamespacedResourceClaimTemplate contentType res accept
`setBodyParam` V1alpha2ResourceClaimTemplate
body

data ReplaceNamespacedResourceClaimTemplate 
instance HasBodyParam ReplaceNamespacedResourceClaimTemplate V1alpha2ResourceClaimTemplate 

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

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

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

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


-- *** replaceNamespacedResourceClassParameters

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/namespaces\/{namespace}\/resourceclassparameters\/{name}@
-- 
-- replace the specified ResourceClassParameters
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceNamespacedResourceClassParameters
  :: (Consumes ReplaceNamespacedResourceClassParameters contentType, MimeRender contentType V1alpha2ResourceClassParameters)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClassParameters -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClassParameters
  -> Namespace -- ^ "namespace" -  object name and auth scope, such as for teams and projects
  -> KubernetesRequest ReplaceNamespacedResourceClassParameters contentType V1alpha2ResourceClassParameters accept
replaceNamespacedResourceClassParameters :: forall contentType accept.
(Consumes ReplaceNamespacedResourceClassParameters contentType,
 MimeRender contentType V1alpha2ResourceClassParameters) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClassParameters
-> Name
-> Namespace
-> KubernetesRequest
     ReplaceNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
replaceNamespacedResourceClassParameters ContentType contentType
_  Accept accept
_ V1alpha2ResourceClassParameters
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclassparameters/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceNamespacedResourceClassParameters
  contentType
  V1alpha2ResourceClassParameters
  accept
-> V1alpha2ResourceClassParameters
-> KubernetesRequest
     ReplaceNamespacedResourceClassParameters
     contentType
     V1alpha2ResourceClassParameters
     accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceNamespacedResourceClassParameters contentType,
 MimeRender contentType V1alpha2ResourceClassParameters) =>
KubernetesRequest
  ReplaceNamespacedResourceClassParameters contentType res accept
-> V1alpha2ResourceClassParameters
-> KubernetesRequest
     ReplaceNamespacedResourceClassParameters contentType res accept
`setBodyParam` V1alpha2ResourceClassParameters
body

data ReplaceNamespacedResourceClassParameters 
instance HasBodyParam ReplaceNamespacedResourceClassParameters V1alpha2ResourceClassParameters 

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

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

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

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


-- *** replaceResourceClass

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/resourceclasses\/{name}@
-- 
-- replace the specified ResourceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceResourceClass
  :: (Consumes ReplaceResourceClass contentType, MimeRender contentType V1alpha2ResourceClass)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceClass -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceClass
  -> KubernetesRequest ReplaceResourceClass contentType V1alpha2ResourceClass accept
replaceResourceClass :: forall contentType accept.
(Consumes ReplaceResourceClass contentType,
 MimeRender contentType V1alpha2ResourceClass) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceClass
-> Name
-> KubernetesRequest
     ReplaceResourceClass contentType V1alpha2ResourceClass accept
replaceResourceClass ContentType contentType
_  Accept accept
_ V1alpha2ResourceClass
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceResourceClass contentType V1alpha2ResourceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceResourceClass contentType V1alpha2ResourceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceResourceClass contentType V1alpha2ResourceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceResourceClass contentType V1alpha2ResourceClass accept
-> V1alpha2ResourceClass
-> KubernetesRequest
     ReplaceResourceClass contentType V1alpha2ResourceClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceResourceClass contentType,
 MimeRender contentType V1alpha2ResourceClass) =>
KubernetesRequest ReplaceResourceClass contentType res accept
-> V1alpha2ResourceClass
-> KubernetesRequest ReplaceResourceClass contentType res accept
`setBodyParam` V1alpha2ResourceClass
body

data ReplaceResourceClass 
instance HasBodyParam ReplaceResourceClass V1alpha2ResourceClass 

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

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

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

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


-- *** replaceResourceSlice

-- | @PUT \/apis\/resource.k8s.io\/v1alpha2\/resourceslices\/{name}@
-- 
-- replace the specified ResourceSlice
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceResourceSlice
  :: (Consumes ReplaceResourceSlice contentType, MimeRender contentType V1alpha2ResourceSlice)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha2ResourceSlice -- ^ "body"
  -> Name -- ^ "name" -  name of the ResourceSlice
  -> KubernetesRequest ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
replaceResourceSlice :: forall contentType accept.
(Consumes ReplaceResourceSlice contentType,
 MimeRender contentType V1alpha2ResourceSlice) =>
ContentType contentType
-> Accept accept
-> V1alpha2ResourceSlice
-> Name
-> KubernetesRequest
     ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
replaceResourceSlice ContentType contentType
_  Accept accept
_ V1alpha2ResourceSlice
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/resource.k8s.io/v1alpha2/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
-> V1alpha2ResourceSlice
-> KubernetesRequest
     ReplaceResourceSlice contentType V1alpha2ResourceSlice accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
forall contentType res accept.
(Consumes ReplaceResourceSlice contentType,
 MimeRender contentType V1alpha2ResourceSlice) =>
KubernetesRequest ReplaceResourceSlice contentType res accept
-> V1alpha2ResourceSlice
-> KubernetesRequest ReplaceResourceSlice contentType res accept
`setBodyParam` V1alpha2ResourceSlice
body

data ReplaceResourceSlice 
instance HasBodyParam ReplaceResourceSlice V1alpha2ResourceSlice 

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

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

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

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