{-
   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.FlowcontrolApiserverV1
-}

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


-- ** FlowcontrolApiserverV1

-- *** createFlowSchema

-- | @POST \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas@
-- 
-- create a FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createFlowSchema
  :: (Consumes CreateFlowSchema contentType, MimeRender contentType V1FlowSchema)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1FlowSchema -- ^ "body"
  -> KubernetesRequest CreateFlowSchema contentType V1FlowSchema accept
createFlowSchema :: forall contentType accept.
(Consumes CreateFlowSchema contentType,
 MimeRender contentType V1FlowSchema) =>
ContentType contentType
-> Accept accept
-> V1FlowSchema
-> KubernetesRequest
     CreateFlowSchema contentType V1FlowSchema accept
createFlowSchema ContentType contentType
_  Accept accept
_ V1FlowSchema
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateFlowSchema contentType V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas"]
    KubernetesRequest CreateFlowSchema contentType V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateFlowSchema contentType V1FlowSchema 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 CreateFlowSchema contentType V1FlowSchema accept
-> V1FlowSchema
-> KubernetesRequest
     CreateFlowSchema contentType V1FlowSchema 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 CreateFlowSchema contentType,
 MimeRender contentType V1FlowSchema) =>
KubernetesRequest CreateFlowSchema contentType res accept
-> V1FlowSchema
-> KubernetesRequest CreateFlowSchema contentType res accept
`setBodyParam` V1FlowSchema
body

data CreateFlowSchema 
instance HasBodyParam CreateFlowSchema V1FlowSchema 

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

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


-- *** createPriorityLevelConfiguration

-- | @POST \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations@
-- 
-- create a PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createPriorityLevelConfiguration
  :: (Consumes CreatePriorityLevelConfiguration contentType, MimeRender contentType V1PriorityLevelConfiguration)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PriorityLevelConfiguration -- ^ "body"
  -> KubernetesRequest CreatePriorityLevelConfiguration contentType V1PriorityLevelConfiguration accept
createPriorityLevelConfiguration :: forall contentType accept.
(Consumes CreatePriorityLevelConfiguration contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     CreatePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     accept
createPriorityLevelConfiguration ContentType contentType
_  Accept accept
_ V1PriorityLevelConfiguration
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreatePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations"]
    KubernetesRequest
  CreatePriorityLevelConfiguration
  contentType
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreatePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     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
  CreatePriorityLevelConfiguration
  contentType
  V1PriorityLevelConfiguration
  accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     CreatePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     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 CreatePriorityLevelConfiguration contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
KubernetesRequest
  CreatePriorityLevelConfiguration contentType res accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     CreatePriorityLevelConfiguration contentType res accept
`setBodyParam` V1PriorityLevelConfiguration
body

data CreatePriorityLevelConfiguration 
instance HasBodyParam CreatePriorityLevelConfiguration V1PriorityLevelConfiguration 

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

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


-- *** deleteCollectionFlowSchema

-- | @DELETE \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas@
-- 
-- delete collection of FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionFlowSchema
  :: (Consumes DeleteCollectionFlowSchema contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionFlowSchema contentType V1Status accept
deleteCollectionFlowSchema :: forall contentType accept.
Consumes DeleteCollectionFlowSchema contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType V1Status accept
deleteCollectionFlowSchema ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas"]
    KubernetesRequest
  DeleteCollectionFlowSchema contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema 
instance HasBodyParam DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (Continue Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (Limit Int
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionFlowSchema SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest DeleteCollectionFlowSchema contentType res accept
req KubernetesRequest DeleteCollectionFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionFlowSchema 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 DeleteCollectionFlowSchema mtype

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


-- *** deleteCollectionPriorityLevelConfiguration

-- | @DELETE \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations@
-- 
-- delete collection of PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionPriorityLevelConfiguration
  :: (Consumes DeleteCollectionPriorityLevelConfiguration contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionPriorityLevelConfiguration contentType V1Status accept
deleteCollectionPriorityLevelConfiguration :: forall contentType accept.
Consumes DeleteCollectionPriorityLevelConfiguration contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration
     contentType
     V1Status
     accept
deleteCollectionPriorityLevelConfiguration ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration
     contentType
     V1Status
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations"]
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration
  contentType
  V1Status
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration
     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 DeleteCollectionPriorityLevelConfiguration 
instance HasBodyParam DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionPriorityLevelConfiguration SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeleteCollectionPriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionPriorityLevelConfiguration 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 DeleteCollectionPriorityLevelConfiguration mtype

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


-- *** deleteFlowSchema

-- | @DELETE \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}@
-- 
-- delete a FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteFlowSchema
  :: (Consumes DeleteFlowSchema contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest DeleteFlowSchema contentType V1Status accept
deleteFlowSchema :: forall contentType accept.
Consumes DeleteFlowSchema contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteFlowSchema contentType V1Status accept
deleteFlowSchema ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteFlowSchema contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteFlowSchema contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteFlowSchema 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 DeleteFlowSchema 
instance HasBodyParam DeleteFlowSchema 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 DeleteFlowSchema Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> Pretty
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteFlowSchema DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> DryRun
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteFlowSchema GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema 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 DeleteFlowSchema IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema 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 DeleteFlowSchema OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema 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 DeleteFlowSchema PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteFlowSchema contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteFlowSchema contentType res accept
applyOptionalParam KubernetesRequest DeleteFlowSchema contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteFlowSchema contentType res accept
req KubernetesRequest DeleteFlowSchema contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteFlowSchema contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteFlowSchema mtype

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


-- *** deletePriorityLevelConfiguration

-- | @DELETE \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}@
-- 
-- delete a PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deletePriorityLevelConfiguration
  :: (Consumes DeletePriorityLevelConfiguration contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest DeletePriorityLevelConfiguration contentType V1Status accept
deletePriorityLevelConfiguration :: forall contentType accept.
Consumes DeletePriorityLevelConfiguration contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType V1Status accept
deletePriorityLevelConfiguration ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeletePriorityLevelConfiguration 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 DeletePriorityLevelConfiguration 
instance HasBodyParam DeletePriorityLevelConfiguration 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 DeletePriorityLevelConfiguration Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> Pretty
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeletePriorityLevelConfiguration DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> DryRun
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeletePriorityLevelConfiguration GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration 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 DeletePriorityLevelConfiguration IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration 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 DeletePriorityLevelConfiguration OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration 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 DeletePriorityLevelConfiguration PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
applyOptionalParam KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
req KubernetesRequest
  DeletePriorityLevelConfiguration contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeletePriorityLevelConfiguration contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeletePriorityLevelConfiguration mtype

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


-- *** getAPIResources

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/@
-- 
-- 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/flowcontrol.apiserver.k8s.io/v1/"]
    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


-- *** listFlowSchema

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas@
-- 
-- list or watch objects of kind FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listFlowSchema
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListFlowSchema MimeNoContent V1FlowSchemaList accept
listFlowSchema :: forall accept.
Accept accept
-> KubernetesRequest
     ListFlowSchema MimeNoContent V1FlowSchemaList accept
listFlowSchema  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListFlowSchema MimeNoContent V1FlowSchemaList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas"]
    KubernetesRequest
  ListFlowSchema MimeNoContent V1FlowSchemaList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListFlowSchema MimeNoContent V1FlowSchemaList 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 ListFlowSchema  

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


-- *** listPriorityLevelConfiguration

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations@
-- 
-- list or watch objects of kind PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listPriorityLevelConfiguration
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListPriorityLevelConfiguration MimeNoContent V1PriorityLevelConfigurationList accept
listPriorityLevelConfiguration :: forall accept.
Accept accept
-> KubernetesRequest
     ListPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfigurationList
     accept
listPriorityLevelConfiguration  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfigurationList
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations"]
    KubernetesRequest
  ListPriorityLevelConfiguration
  MimeNoContent
  V1PriorityLevelConfigurationList
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfigurationList
     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 ListPriorityLevelConfiguration  

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


-- *** patchFlowSchema

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

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

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


-- *** patchFlowSchemaStatus

-- | @PATCH \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}\/status@
-- 
-- partially update status of the specified FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchFlowSchemaStatus
  :: (Consumes PatchFlowSchemaStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest PatchFlowSchemaStatus contentType V1FlowSchema accept
patchFlowSchemaStatus :: forall contentType accept.
(Consumes PatchFlowSchemaStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchFlowSchemaStatus contentType V1FlowSchema accept
patchFlowSchemaStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchFlowSchemaStatus contentType V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchFlowSchemaStatus contentType V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchFlowSchemaStatus contentType V1FlowSchema 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
  PatchFlowSchemaStatus contentType V1FlowSchema accept
-> Body
-> KubernetesRequest
     PatchFlowSchemaStatus contentType V1FlowSchema 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 PatchFlowSchemaStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchFlowSchemaStatus contentType res accept
-> Body
-> KubernetesRequest PatchFlowSchemaStatus contentType res accept
`setBodyParam` Body
body

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

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


-- *** patchPriorityLevelConfiguration

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

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

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


-- *** patchPriorityLevelConfigurationStatus

-- | @PATCH \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}\/status@
-- 
-- partially update status of the specified PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchPriorityLevelConfigurationStatus
  :: (Consumes PatchPriorityLevelConfigurationStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest PatchPriorityLevelConfigurationStatus contentType V1PriorityLevelConfiguration accept
patchPriorityLevelConfigurationStatus :: forall contentType accept.
(Consumes PatchPriorityLevelConfigurationStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchPriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     accept
patchPriorityLevelConfigurationStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchPriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchPriorityLevelConfigurationStatus
  contentType
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchPriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     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
  PatchPriorityLevelConfigurationStatus
  contentType
  V1PriorityLevelConfiguration
  accept
-> Body
-> KubernetesRequest
     PatchPriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     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 PatchPriorityLevelConfigurationStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest
  PatchPriorityLevelConfigurationStatus contentType res accept
-> Body
-> KubernetesRequest
     PatchPriorityLevelConfigurationStatus contentType res accept
`setBodyParam` Body
body

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

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


-- *** readFlowSchema

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}@
-- 
-- read the specified FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readFlowSchema
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest ReadFlowSchema MimeNoContent V1FlowSchema accept
readFlowSchema :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadFlowSchema MimeNoContent V1FlowSchema accept
readFlowSchema  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadFlowSchema MimeNoContent V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReadFlowSchema MimeNoContent V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadFlowSchema MimeNoContent V1FlowSchema 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 ReadFlowSchema  

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


-- *** readFlowSchemaStatus

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}\/status@
-- 
-- read status of the specified FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readFlowSchemaStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest ReadFlowSchemaStatus MimeNoContent V1FlowSchema accept
readFlowSchemaStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadFlowSchemaStatus MimeNoContent V1FlowSchema accept
readFlowSchemaStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadFlowSchemaStatus MimeNoContent V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadFlowSchemaStatus MimeNoContent V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadFlowSchemaStatus MimeNoContent V1FlowSchema 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 ReadFlowSchemaStatus  

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


-- *** readPriorityLevelConfiguration

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}@
-- 
-- read the specified PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readPriorityLevelConfiguration
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest ReadPriorityLevelConfiguration MimeNoContent V1PriorityLevelConfiguration accept
readPriorityLevelConfiguration :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfiguration
     accept
readPriorityLevelConfiguration  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadPriorityLevelConfiguration
  MimeNoContent
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadPriorityLevelConfiguration
     MimeNoContent
     V1PriorityLevelConfiguration
     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 ReadPriorityLevelConfiguration  

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


-- *** readPriorityLevelConfigurationStatus

-- | @GET \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}\/status@
-- 
-- read status of the specified PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readPriorityLevelConfigurationStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest ReadPriorityLevelConfigurationStatus MimeNoContent V1PriorityLevelConfiguration accept
readPriorityLevelConfigurationStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadPriorityLevelConfigurationStatus
     MimeNoContent
     V1PriorityLevelConfiguration
     accept
readPriorityLevelConfigurationStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadPriorityLevelConfigurationStatus
     MimeNoContent
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadPriorityLevelConfigurationStatus
  MimeNoContent
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadPriorityLevelConfigurationStatus
     MimeNoContent
     V1PriorityLevelConfiguration
     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 ReadPriorityLevelConfigurationStatus  

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


-- *** replaceFlowSchema

-- | @PUT \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}@
-- 
-- replace the specified FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceFlowSchema
  :: (Consumes ReplaceFlowSchema contentType, MimeRender contentType V1FlowSchema)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1FlowSchema -- ^ "body"
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest ReplaceFlowSchema contentType V1FlowSchema accept
replaceFlowSchema :: forall contentType accept.
(Consumes ReplaceFlowSchema contentType,
 MimeRender contentType V1FlowSchema) =>
ContentType contentType
-> Accept accept
-> V1FlowSchema
-> Name
-> KubernetesRequest
     ReplaceFlowSchema contentType V1FlowSchema accept
replaceFlowSchema ContentType contentType
_  Accept accept
_ V1FlowSchema
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceFlowSchema contentType V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest ReplaceFlowSchema contentType V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceFlowSchema contentType V1FlowSchema 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 ReplaceFlowSchema contentType V1FlowSchema accept
-> V1FlowSchema
-> KubernetesRequest
     ReplaceFlowSchema contentType V1FlowSchema 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 ReplaceFlowSchema contentType,
 MimeRender contentType V1FlowSchema) =>
KubernetesRequest ReplaceFlowSchema contentType res accept
-> V1FlowSchema
-> KubernetesRequest ReplaceFlowSchema contentType res accept
`setBodyParam` V1FlowSchema
body

data ReplaceFlowSchema 
instance HasBodyParam ReplaceFlowSchema V1FlowSchema 

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

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


-- *** replaceFlowSchemaStatus

-- | @PUT \/apis\/flowcontrol.apiserver.k8s.io\/v1\/flowschemas\/{name}\/status@
-- 
-- replace status of the specified FlowSchema
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceFlowSchemaStatus
  :: (Consumes ReplaceFlowSchemaStatus contentType, MimeRender contentType V1FlowSchema)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1FlowSchema -- ^ "body"
  -> Name -- ^ "name" -  name of the FlowSchema
  -> KubernetesRequest ReplaceFlowSchemaStatus contentType V1FlowSchema accept
replaceFlowSchemaStatus :: forall contentType accept.
(Consumes ReplaceFlowSchemaStatus contentType,
 MimeRender contentType V1FlowSchema) =>
ContentType contentType
-> Accept accept
-> V1FlowSchema
-> Name
-> KubernetesRequest
     ReplaceFlowSchemaStatus contentType V1FlowSchema accept
replaceFlowSchemaStatus ContentType contentType
_  Accept accept
_ V1FlowSchema
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceFlowSchemaStatus contentType V1FlowSchema accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/flowschemas/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceFlowSchemaStatus contentType V1FlowSchema accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceFlowSchemaStatus contentType V1FlowSchema 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
  ReplaceFlowSchemaStatus contentType V1FlowSchema accept
-> V1FlowSchema
-> KubernetesRequest
     ReplaceFlowSchemaStatus contentType V1FlowSchema 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 ReplaceFlowSchemaStatus contentType,
 MimeRender contentType V1FlowSchema) =>
KubernetesRequest ReplaceFlowSchemaStatus contentType res accept
-> V1FlowSchema
-> KubernetesRequest ReplaceFlowSchemaStatus contentType res accept
`setBodyParam` V1FlowSchema
body

data ReplaceFlowSchemaStatus 
instance HasBodyParam ReplaceFlowSchemaStatus V1FlowSchema 

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

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


-- *** replacePriorityLevelConfiguration

-- | @PUT \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}@
-- 
-- replace the specified PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replacePriorityLevelConfiguration
  :: (Consumes ReplacePriorityLevelConfiguration contentType, MimeRender contentType V1PriorityLevelConfiguration)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PriorityLevelConfiguration -- ^ "body"
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest ReplacePriorityLevelConfiguration contentType V1PriorityLevelConfiguration accept
replacePriorityLevelConfiguration :: forall contentType accept.
(Consumes ReplacePriorityLevelConfiguration contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> Name
-> KubernetesRequest
     ReplacePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     accept
replacePriorityLevelConfiguration ContentType contentType
_  Accept accept
_ V1PriorityLevelConfiguration
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplacePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplacePriorityLevelConfiguration
  contentType
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplacePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     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
  ReplacePriorityLevelConfiguration
  contentType
  V1PriorityLevelConfiguration
  accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     ReplacePriorityLevelConfiguration
     contentType
     V1PriorityLevelConfiguration
     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 ReplacePriorityLevelConfiguration contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
KubernetesRequest
  ReplacePriorityLevelConfiguration contentType res accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     ReplacePriorityLevelConfiguration contentType res accept
`setBodyParam` V1PriorityLevelConfiguration
body

data ReplacePriorityLevelConfiguration 
instance HasBodyParam ReplacePriorityLevelConfiguration V1PriorityLevelConfiguration 

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

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


-- *** replacePriorityLevelConfigurationStatus

-- | @PUT \/apis\/flowcontrol.apiserver.k8s.io\/v1\/prioritylevelconfigurations\/{name}\/status@
-- 
-- replace status of the specified PriorityLevelConfiguration
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replacePriorityLevelConfigurationStatus
  :: (Consumes ReplacePriorityLevelConfigurationStatus contentType, MimeRender contentType V1PriorityLevelConfiguration)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1PriorityLevelConfiguration -- ^ "body"
  -> Name -- ^ "name" -  name of the PriorityLevelConfiguration
  -> KubernetesRequest ReplacePriorityLevelConfigurationStatus contentType V1PriorityLevelConfiguration accept
replacePriorityLevelConfigurationStatus :: forall contentType accept.
(Consumes ReplacePriorityLevelConfigurationStatus contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> Name
-> KubernetesRequest
     ReplacePriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     accept
replacePriorityLevelConfigurationStatus ContentType contentType
_  Accept accept
_ V1PriorityLevelConfiguration
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplacePriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/flowcontrol.apiserver.k8s.io/v1/prioritylevelconfigurations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplacePriorityLevelConfigurationStatus
  contentType
  V1PriorityLevelConfiguration
  accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplacePriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     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
  ReplacePriorityLevelConfigurationStatus
  contentType
  V1PriorityLevelConfiguration
  accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     ReplacePriorityLevelConfigurationStatus
     contentType
     V1PriorityLevelConfiguration
     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 ReplacePriorityLevelConfigurationStatus contentType,
 MimeRender contentType V1PriorityLevelConfiguration) =>
KubernetesRequest
  ReplacePriorityLevelConfigurationStatus contentType res accept
-> V1PriorityLevelConfiguration
-> KubernetesRequest
     ReplacePriorityLevelConfigurationStatus contentType res accept
`setBodyParam` V1PriorityLevelConfiguration
body

data ReplacePriorityLevelConfigurationStatus 
instance HasBodyParam ReplacePriorityLevelConfigurationStatus V1PriorityLevelConfiguration 

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

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