{-
   Kubernetes

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

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

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

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


-- ** ResourceV1alpha3

-- *** createDeviceClass

-- | @POST \/apis\/resource.k8s.io\/v1alpha3\/deviceclasses@
-- 
-- create a DeviceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createDeviceClass
  :: (Consumes CreateDeviceClass contentType, MimeRender contentType V1alpha3DeviceClass)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1alpha3DeviceClass -- ^ "body"
  -> KubernetesRequest CreateDeviceClass contentType V1alpha3DeviceClass accept
createDeviceClass :: forall contentType accept.
(Consumes CreateDeviceClass contentType,
 MimeRender contentType V1alpha3DeviceClass) =>
ContentType contentType
-> Accept accept
-> V1alpha3DeviceClass
-> KubernetesRequest
     CreateDeviceClass contentType V1alpha3DeviceClass accept
createDeviceClass ContentType contentType
_  Accept accept
_ V1alpha3DeviceClass
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateDeviceClass contentType V1alpha3DeviceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/resource.k8s.io/v1alpha3/deviceclasses"]
    KubernetesRequest
  CreateDeviceClass contentType V1alpha3DeviceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateDeviceClass contentType V1alpha3DeviceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  CreateDeviceClass contentType V1alpha3DeviceClass accept
-> V1alpha3DeviceClass
-> KubernetesRequest
     CreateDeviceClass contentType V1alpha3DeviceClass 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 CreateDeviceClass contentType,
 MimeRender contentType V1alpha3DeviceClass) =>
KubernetesRequest CreateDeviceClass contentType res accept
-> V1alpha3DeviceClass
-> KubernetesRequest CreateDeviceClass contentType res accept
`setBodyParam` V1alpha3DeviceClass
body

data CreateDeviceClass 
instance HasBodyParam CreateDeviceClass V1alpha3DeviceClass 

-- | /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 CreateDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest CreateDeviceClass contentType res accept
applyOptionalParam KubernetesRequest CreateDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateDeviceClass contentType res accept
req KubernetesRequest CreateDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateDeviceClass DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateDeviceClass contentType res accept
-> DryRun
-> KubernetesRequest CreateDeviceClass contentType res accept
applyOptionalParam KubernetesRequest CreateDeviceClass contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateDeviceClass contentType res accept
req KubernetesRequest CreateDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateDeviceClass FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateDeviceClass contentType res accept
-> FieldManager
-> KubernetesRequest CreateDeviceClass contentType res accept
applyOptionalParam KubernetesRequest CreateDeviceClass contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateDeviceClass contentType res accept
req KubernetesRequest CreateDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateDeviceClass FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateDeviceClass contentType res accept
-> FieldValidation
-> KubernetesRequest CreateDeviceClass contentType res accept
applyOptionalParam KubernetesRequest CreateDeviceClass contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateDeviceClass contentType res accept
req KubernetesRequest CreateDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateDeviceClass mtype

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


-- *** createNamespacedResourceClaim

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

data CreateNamespacedResourceClaim 
instance HasBodyParam CreateNamespacedResourceClaim V1alpha3ResourceClaim 

-- | /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/cbor@
instance Produces CreateNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedResourceClaim MimeYaml


-- *** createNamespacedResourceClaimTemplate

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

data CreateNamespacedResourceClaimTemplate 
instance HasBodyParam CreateNamespacedResourceClaimTemplate V1alpha3ResourceClaimTemplate 

-- | /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/cbor@
instance Produces CreateNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces CreateNamespacedResourceClaimTemplate MimeYaml


-- *** createResourceSlice

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

data CreateResourceSlice 
instance HasBodyParam CreateResourceSlice V1alpha3ResourceSlice 

-- | /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/cbor@
instance Produces CreateResourceSlice MimeCbor
-- | @application/yaml@
instance Produces CreateResourceSlice MimeYaml


-- *** deleteCollectionDeviceClass

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha3\/deviceclasses@
-- 
-- delete collection of DeviceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionDeviceClass
  :: (Consumes DeleteCollectionDeviceClass contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionDeviceClass contentType V1Status accept
deleteCollectionDeviceClass :: forall contentType accept.
Consumes DeleteCollectionDeviceClass contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType V1Status accept
deleteCollectionDeviceClass ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha3/deviceclasses"]
    KubernetesRequest
  DeleteCollectionDeviceClass contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionDeviceClass 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 DeleteCollectionDeviceClass 
instance HasBodyParam DeleteCollectionDeviceClass 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 DeleteCollectionDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

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

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionDeviceClass LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass 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 DeleteCollectionDeviceClass OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionDeviceClass TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionDeviceClass contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
req KubernetesRequest
  DeleteCollectionDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionDeviceClass 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 DeleteCollectionDeviceClass mtype

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


-- *** deleteCollectionNamespacedResourceClaim

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

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam 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/cbor@
instance Produces DeleteCollectionNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedResourceClaim MimeYaml


-- *** deleteCollectionNamespacedResourceClaimTemplate

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

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam 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/cbor@
instance Produces DeleteCollectionNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionNamespacedResourceClaimTemplate MimeYaml


-- *** deleteCollectionResourceSlice

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

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam 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/cbor@
instance Produces DeleteCollectionResourceSlice MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionResourceSlice MimeYaml


-- *** deleteDeviceClass

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha3\/deviceclasses\/{name}@
-- 
-- delete a DeviceClass
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteDeviceClass
  :: (Consumes DeleteDeviceClass contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the DeviceClass
  -> KubernetesRequest DeleteDeviceClass contentType V1alpha3DeviceClass accept
deleteDeviceClass :: forall contentType accept.
Consumes DeleteDeviceClass contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeleteDeviceClass contentType V1alpha3DeviceClass accept
deleteDeviceClass ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteDeviceClass contentType V1alpha3DeviceClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha3/deviceclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteDeviceClass contentType V1alpha3DeviceClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteDeviceClass contentType V1alpha3DeviceClass accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 DeleteDeviceClass 
instance HasBodyParam DeleteDeviceClass 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 DeleteDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest DeleteDeviceClass contentType res accept
applyOptionalParam KubernetesRequest DeleteDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteDeviceClass contentType res accept
req KubernetesRequest DeleteDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteDeviceClass DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteDeviceClass contentType res accept
-> DryRun
-> KubernetesRequest DeleteDeviceClass contentType res accept
applyOptionalParam KubernetesRequest DeleteDeviceClass contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteDeviceClass contentType res accept
req KubernetesRequest DeleteDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteDeviceClass GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteDeviceClass contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteDeviceClass contentType res accept
applyOptionalParam KubernetesRequest DeleteDeviceClass contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteDeviceClass contentType res accept
req KubernetesRequest DeleteDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

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

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

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


-- *** deleteNamespacedResourceClaim

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaim accept
deleteNamespacedResourceClaim :: forall contentType accept.
Consumes DeleteNamespacedResourceClaim contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
deleteNamespacedResourceClaim ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedResourceClaim IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceClaim contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedResourceClaim contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceClaim contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam 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/cbor@
instance Produces DeleteNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedResourceClaim MimeYaml


-- *** deleteNamespacedResourceClaimTemplate

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaimTemplate accept
deleteNamespacedResourceClaimTemplate :: forall contentType accept.
Consumes DeleteNamespacedResourceClaimTemplate contentType =>
ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
deleteNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteNamespacedResourceClaimTemplate IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteNamespacedResourceClaimTemplate contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteNamespacedResourceClaimTemplate contentType res accept
applyOptionalParam KubernetesRequest
  DeleteNamespacedResourceClaimTemplate contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam 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/cbor@
instance Produces DeleteNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces DeleteNamespacedResourceClaimTemplate MimeYaml


-- *** deleteResourceSlice

-- | @DELETE \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceSlice accept
deleteResourceSlice :: forall contentType accept.
Consumes DeleteResourceSlice contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha3ResourceSlice accept
deleteResourceSlice ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha3ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/resource.k8s.io/v1alpha3/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeleteResourceSlice contentType V1alpha3ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteResourceSlice contentType V1alpha3ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteResourceSlice IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteResourceSlice contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteResourceSlice contentType res accept
applyOptionalParam KubernetesRequest DeleteResourceSlice contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam 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/cbor@
instance Produces DeleteResourceSlice MimeCbor
-- | @application/yaml@
instance Produces DeleteResourceSlice MimeYaml


-- *** getAPIResources

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/@
-- 
-- 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/v1alpha3/"]
    KubernetesRequest
  GetAPIResources MimeNoContent V1APIResourceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

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


-- *** listDeviceClass

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

-- | /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 ListDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> Continue
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> FieldSelector
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> LabelSelector
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> Limit
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass 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 ListDeviceClass ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> ResourceVersion
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListDeviceClass TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass 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 ListDeviceClass Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListDeviceClass contentType res accept
-> Watch
-> KubernetesRequest ListDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ListDeviceClass contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListDeviceClass contentType res accept
req KubernetesRequest ListDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/cbor-seq@
instance Produces ListDeviceClass MimeCborSeq
-- | @application/json@
instance Produces ListDeviceClass MimeJSON
-- | @application/json;stream=watch@
instance Produces ListDeviceClass MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListDeviceClass MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListDeviceClass MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListDeviceClass MimeCbor
-- | @application/yaml@
instance Produces ListDeviceClass MimeYaml


-- *** listNamespacedResourceClaim

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaimList accept
listNamespacedResourceClaim :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaimList
     accept
listNamespacedResourceClaim  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaimList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha3/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaims"]
    KubernetesRequest
  ListNamespacedResourceClaim
  MimeNoContent
  V1alpha3ResourceClaimList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaimList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/cbor-seq@
instance Produces ListNamespacedResourceClaim MimeCborSeq
-- | @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/cbor@
instance Produces ListNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedResourceClaim MimeYaml


-- *** listNamespacedResourceClaimTemplate

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaimTemplateList accept
listNamespacedResourceClaimTemplate :: forall accept.
Accept accept
-> Namespace
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplateList
     accept
listNamespacedResourceClaimTemplate  Accept accept
_ (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplateList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha3/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/resourceclaimtemplates"]
    KubernetesRequest
  ListNamespacedResourceClaimTemplate
  MimeNoContent
  V1alpha3ResourceClaimTemplateList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplateList
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/cbor-seq@
instance Produces ListNamespacedResourceClaimTemplate MimeCborSeq
-- | @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/cbor@
instance Produces ListNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces ListNamespacedResourceClaimTemplate MimeYaml


-- *** listResourceClaimForAllNamespaces

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


-- *** listResourceClaimTemplateForAllNamespaces

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


-- *** listResourceSlice

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


-- *** patchDeviceClass

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

data PatchDeviceClass 
instance HasBodyParam PatchDeviceClass 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 PatchDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest PatchDeviceClass contentType res accept
applyOptionalParam KubernetesRequest PatchDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchDeviceClass contentType res accept
req KubernetesRequest PatchDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchDeviceClass DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchDeviceClass contentType res accept
-> DryRun
-> KubernetesRequest PatchDeviceClass contentType res accept
applyOptionalParam KubernetesRequest PatchDeviceClass contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchDeviceClass contentType res accept
req KubernetesRequest PatchDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchDeviceClass FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchDeviceClass contentType res accept
-> FieldManager
-> KubernetesRequest PatchDeviceClass contentType res accept
applyOptionalParam KubernetesRequest PatchDeviceClass contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchDeviceClass contentType res accept
req KubernetesRequest PatchDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchDeviceClass FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchDeviceClass contentType res accept
-> FieldValidation
-> KubernetesRequest PatchDeviceClass contentType res accept
applyOptionalParam KubernetesRequest PatchDeviceClass contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchDeviceClass contentType res accept
req KubernetesRequest PatchDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchDeviceClass Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchDeviceClass contentType res accept
-> Force
-> KubernetesRequest PatchDeviceClass contentType res accept
applyOptionalParam KubernetesRequest PatchDeviceClass contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchDeviceClass contentType res accept
req KubernetesRequest PatchDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchDeviceClass MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchDeviceClass MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchDeviceClass MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchDeviceClass MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchDeviceClass MimeApplyPatchcbor

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


-- *** patchNamespacedResourceClaim

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaim accept
patchNamespacedResourceClaim :: forall contentType accept.
(Consumes PatchNamespacedResourceClaim contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
patchNamespacedResourceClaim ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  V1alpha3ResourceClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaim
     contentType
     V1alpha3ResourceClaim
     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/apply-patch+cbor@
instance Consumes PatchNamespacedResourceClaim MimeApplyPatchcbor

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


-- *** patchNamespacedResourceClaimStatus

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaim accept
patchNamespacedResourceClaimStatus :: forall contentType accept.
(Consumes PatchNamespacedResourceClaimStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha3ResourceClaim
     accept
patchNamespacedResourceClaimStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha3ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha3ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  V1alpha3ResourceClaim
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimStatus
     contentType
     V1alpha3ResourceClaim
     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/apply-patch+cbor@
instance Consumes PatchNamespacedResourceClaimStatus MimeApplyPatchcbor

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


-- *** patchNamespacedResourceClaimTemplate

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaimTemplate accept
patchNamespacedResourceClaimTemplate :: forall contentType accept.
(Consumes PatchNamespacedResourceClaimTemplate contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> Namespace
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
patchNamespacedResourceClaimTemplate ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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
  V1alpha3ResourceClaimTemplate
  accept
-> Body
-> KubernetesRequest
     PatchNamespacedResourceClaimTemplate
     contentType
     V1alpha3ResourceClaimTemplate
     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/apply-patch+cbor@
instance Consumes PatchNamespacedResourceClaimTemplate MimeApplyPatchcbor

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


-- *** patchResourceSlice

-- | @PATCH \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceSlice accept
patchResourceSlice :: forall contentType accept.
(Consumes PatchResourceSlice contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha3ResourceSlice accept
patchResourceSlice ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha3ResourceSlice accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/resource.k8s.io/v1alpha3/resourceslices/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchResourceSlice contentType V1alpha3ResourceSlice accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha3ResourceSlice accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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 V1alpha3ResourceSlice accept
-> Body
-> KubernetesRequest
     PatchResourceSlice contentType V1alpha3ResourceSlice 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/apply-patch+cbor@
instance Consumes PatchResourceSlice MimeApplyPatchcbor

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


-- *** readDeviceClass

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

-- | /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 ReadDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest ReadDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ReadDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadDeviceClass contentType res accept
req KubernetesRequest ReadDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReadDeviceClass MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadDeviceClass MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadDeviceClass MimeCbor
-- | @application/yaml@
instance Produces ReadDeviceClass MimeYaml


-- *** readNamespacedResourceClaim

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaim accept
readNamespacedResourceClaim :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaim
     accept
readNamespacedResourceClaim  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaim
     MimeNoContent
     V1alpha3ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/cbor@
instance Produces ReadNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedResourceClaim MimeYaml


-- *** readNamespacedResourceClaimStatus

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaim accept
readNamespacedResourceClaimStatus :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha3ResourceClaim
     accept
readNamespacedResourceClaimStatus  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha3ResourceClaim
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaim
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaimStatus
     MimeNoContent
     V1alpha3ResourceClaim
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/cbor@
instance Produces ReadNamespacedResourceClaimStatus MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedResourceClaimStatus MimeYaml


-- *** readNamespacedResourceClaimTemplate

-- | @GET \/apis\/resource.k8s.io\/v1alpha3\/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 V1alpha3ResourceClaimTemplate accept
readNamespacedResourceClaimTemplate :: forall accept.
Accept accept
-> Name
-> Namespace
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplate
     accept
readNamespacedResourceClaimTemplate  Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplate
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/resource.k8s.io/v1alpha3/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
  V1alpha3ResourceClaimTemplate
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadNamespacedResourceClaimTemplate
     MimeNoContent
     V1alpha3ResourceClaimTemplate
     accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req 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/cbor@
instance Produces ReadNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces ReadNamespacedResourceClaimTemplate MimeYaml


-- *** readResourceSlice

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


-- *** replaceDeviceClass

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

data ReplaceDeviceClass 
instance HasBodyParam ReplaceDeviceClass V1alpha3DeviceClass 

-- | /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 ReplaceDeviceClass Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceDeviceClass contentType res accept
-> Pretty
-> KubernetesRequest ReplaceDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceDeviceClass contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceDeviceClass contentType res accept
req KubernetesRequest ReplaceDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceDeviceClass DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceDeviceClass contentType res accept
-> DryRun
-> KubernetesRequest ReplaceDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceDeviceClass contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceDeviceClass contentType res accept
req KubernetesRequest ReplaceDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceDeviceClass FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceDeviceClass contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceDeviceClass contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceDeviceClass contentType res accept
req KubernetesRequest ReplaceDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceDeviceClass FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceDeviceClass contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceDeviceClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceDeviceClass contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceDeviceClass contentType res accept
req KubernetesRequest ReplaceDeviceClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceDeviceClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceDeviceClass mtype

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


-- *** replaceNamespacedResourceClaim

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

data ReplaceNamespacedResourceClaim 
instance HasBodyParam ReplaceNamespacedResourceClaim V1alpha3ResourceClaim 

-- | /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/cbor@
instance Produces ReplaceNamespacedResourceClaim MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedResourceClaim MimeYaml


-- *** replaceNamespacedResourceClaimStatus

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

data ReplaceNamespacedResourceClaimStatus 
instance HasBodyParam ReplaceNamespacedResourceClaimStatus V1alpha3ResourceClaim 

-- | /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/cbor@
instance Produces ReplaceNamespacedResourceClaimStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedResourceClaimStatus MimeYaml


-- *** replaceNamespacedResourceClaimTemplate

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

data ReplaceNamespacedResourceClaimTemplate 
instance HasBodyParam ReplaceNamespacedResourceClaimTemplate V1alpha3ResourceClaimTemplate 

-- | /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/cbor@
instance Produces ReplaceNamespacedResourceClaimTemplate MimeCbor
-- | @application/yaml@
instance Produces ReplaceNamespacedResourceClaimTemplate MimeYaml


-- *** replaceResourceSlice

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

data ReplaceResourceSlice 
instance HasBodyParam ReplaceResourceSlice V1alpha3ResourceSlice 

-- | /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/cbor@
instance Produces ReplaceResourceSlice MimeCbor
-- | @application/yaml@
instance Produces ReplaceResourceSlice MimeYaml