{-# 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
createFlowSchema
:: (Consumes CreateFlowSchema contentType, MimeRender contentType V1FlowSchema)
=> ContentType contentType
-> Accept accept
-> V1FlowSchema
-> 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
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)
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)
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)
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
instance Produces CreateFlowSchema MimeJSON
instance Produces CreateFlowSchema MimeVndKubernetesProtobuf
instance Produces CreateFlowSchema MimeCbor
instance Produces CreateFlowSchema MimeYaml
createPriorityLevelConfiguration
:: (Consumes CreatePriorityLevelConfiguration contentType, MimeRender contentType V1PriorityLevelConfiguration)
=> ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> 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
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)
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)
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)
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
instance Produces CreatePriorityLevelConfiguration MimeJSON
instance Produces CreatePriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces CreatePriorityLevelConfiguration MimeCbor
instance Produces CreatePriorityLevelConfiguration MimeYaml
deleteCollectionFlowSchema
:: (Consumes DeleteCollectionFlowSchema contentType)
=> ContentType contentType
-> Accept accept
-> 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
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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
instance Produces DeleteCollectionFlowSchema MimeJSON
instance Produces DeleteCollectionFlowSchema MimeVndKubernetesProtobuf
instance Produces DeleteCollectionFlowSchema MimeCbor
instance Produces DeleteCollectionFlowSchema MimeYaml
deleteCollectionPriorityLevelConfiguration
:: (Consumes DeleteCollectionPriorityLevelConfiguration contentType)
=> ContentType contentType
-> Accept accept
-> 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
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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
instance Produces DeleteCollectionPriorityLevelConfiguration MimeJSON
instance Produces DeleteCollectionPriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces DeleteCollectionPriorityLevelConfiguration MimeCbor
instance Produces DeleteCollectionPriorityLevelConfiguration MimeYaml
deleteFlowSchema
:: (Consumes DeleteFlowSchema contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> 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
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)
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)
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)
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)
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)
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
instance Produces DeleteFlowSchema MimeJSON
instance Produces DeleteFlowSchema MimeVndKubernetesProtobuf
instance Produces DeleteFlowSchema MimeCbor
instance Produces DeleteFlowSchema MimeYaml
deletePriorityLevelConfiguration
:: (Consumes DeletePriorityLevelConfiguration contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> 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
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)
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)
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)
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)
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)
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
instance Produces DeletePriorityLevelConfiguration MimeJSON
instance Produces DeletePriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces DeletePriorityLevelConfiguration MimeCbor
instance Produces DeletePriorityLevelConfiguration MimeYaml
getAPIResources
:: Accept accept
-> 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
instance Produces GetAPIResources MimeJSON
instance Produces GetAPIResources MimeVndKubernetesProtobuf
instance Produces GetAPIResources MimeCbor
instance Produces GetAPIResources MimeYaml
listFlowSchema
:: Accept accept
-> 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
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
instance Produces ListFlowSchema MimeCborSeq
instance Produces ListFlowSchema MimeJSON
instance Produces ListFlowSchema MimeJsonstreamwatch
instance Produces ListFlowSchema MimeVndKubernetesProtobuf
instance Produces ListFlowSchema MimeVndKubernetesProtobufstreamwatch
instance Produces ListFlowSchema MimeCbor
instance Produces ListFlowSchema MimeYaml
listPriorityLevelConfiguration
:: Accept accept
-> 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
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
instance Produces ListPriorityLevelConfiguration MimeCborSeq
instance Produces ListPriorityLevelConfiguration MimeJSON
instance Produces ListPriorityLevelConfiguration MimeJsonstreamwatch
instance Produces ListPriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces ListPriorityLevelConfiguration MimeVndKubernetesProtobufstreamwatch
instance Produces ListPriorityLevelConfiguration MimeCbor
instance Produces ListPriorityLevelConfiguration MimeYaml
patchFlowSchema
:: (Consumes PatchFlowSchema contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> 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
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)
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)
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)
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)
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)
instance Consumes PatchFlowSchema MimeApplyPatchyaml
instance Consumes PatchFlowSchema MimeJsonPatchjson
instance Consumes PatchFlowSchema MimeMergePatchjson
instance Consumes PatchFlowSchema MimeStrategicMergePatchjson
instance Consumes PatchFlowSchema MimeApplyPatchcbor
instance Produces PatchFlowSchema MimeJSON
instance Produces PatchFlowSchema MimeVndKubernetesProtobuf
instance Produces PatchFlowSchema MimeCbor
instance Produces PatchFlowSchema MimeYaml
patchFlowSchemaStatus
:: (Consumes PatchFlowSchemaStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> 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
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)
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)
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)
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)
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)
instance Consumes PatchFlowSchemaStatus MimeApplyPatchyaml
instance Consumes PatchFlowSchemaStatus MimeJsonPatchjson
instance Consumes PatchFlowSchemaStatus MimeMergePatchjson
instance Consumes PatchFlowSchemaStatus MimeStrategicMergePatchjson
instance Consumes PatchFlowSchemaStatus MimeApplyPatchcbor
instance Produces PatchFlowSchemaStatus MimeJSON
instance Produces PatchFlowSchemaStatus MimeVndKubernetesProtobuf
instance Produces PatchFlowSchemaStatus MimeCbor
instance Produces PatchFlowSchemaStatus MimeYaml
patchPriorityLevelConfiguration
:: (Consumes PatchPriorityLevelConfiguration contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> 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
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)
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)
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)
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)
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)
instance Consumes PatchPriorityLevelConfiguration MimeApplyPatchyaml
instance Consumes PatchPriorityLevelConfiguration MimeJsonPatchjson
instance Consumes PatchPriorityLevelConfiguration MimeMergePatchjson
instance Consumes PatchPriorityLevelConfiguration MimeStrategicMergePatchjson
instance Consumes PatchPriorityLevelConfiguration MimeApplyPatchcbor
instance Produces PatchPriorityLevelConfiguration MimeJSON
instance Produces PatchPriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces PatchPriorityLevelConfiguration MimeCbor
instance Produces PatchPriorityLevelConfiguration MimeYaml
patchPriorityLevelConfigurationStatus
:: (Consumes PatchPriorityLevelConfigurationStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> 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
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)
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)
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)
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)
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)
instance Consumes PatchPriorityLevelConfigurationStatus MimeApplyPatchyaml
instance Consumes PatchPriorityLevelConfigurationStatus MimeJsonPatchjson
instance Consumes PatchPriorityLevelConfigurationStatus MimeMergePatchjson
instance Consumes PatchPriorityLevelConfigurationStatus MimeStrategicMergePatchjson
instance Consumes PatchPriorityLevelConfigurationStatus MimeApplyPatchcbor
instance Produces PatchPriorityLevelConfigurationStatus MimeJSON
instance Produces PatchPriorityLevelConfigurationStatus MimeVndKubernetesProtobuf
instance Produces PatchPriorityLevelConfigurationStatus MimeCbor
instance Produces PatchPriorityLevelConfigurationStatus MimeYaml
readFlowSchema
:: Accept accept
-> Name
-> 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
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)
instance Produces ReadFlowSchema MimeJSON
instance Produces ReadFlowSchema MimeVndKubernetesProtobuf
instance Produces ReadFlowSchema MimeCbor
instance Produces ReadFlowSchema MimeYaml
readFlowSchemaStatus
:: Accept accept
-> Name
-> 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
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)
instance Produces ReadFlowSchemaStatus MimeJSON
instance Produces ReadFlowSchemaStatus MimeVndKubernetesProtobuf
instance Produces ReadFlowSchemaStatus MimeCbor
instance Produces ReadFlowSchemaStatus MimeYaml
readPriorityLevelConfiguration
:: Accept accept
-> Name
-> 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
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)
instance Produces ReadPriorityLevelConfiguration MimeJSON
instance Produces ReadPriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces ReadPriorityLevelConfiguration MimeCbor
instance Produces ReadPriorityLevelConfiguration MimeYaml
readPriorityLevelConfigurationStatus
:: Accept accept
-> Name
-> 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
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)
instance Produces ReadPriorityLevelConfigurationStatus MimeJSON
instance Produces ReadPriorityLevelConfigurationStatus MimeVndKubernetesProtobuf
instance Produces ReadPriorityLevelConfigurationStatus MimeCbor
instance Produces ReadPriorityLevelConfigurationStatus MimeYaml
replaceFlowSchema
:: (Consumes ReplaceFlowSchema contentType, MimeRender contentType V1FlowSchema)
=> ContentType contentType
-> Accept accept
-> V1FlowSchema
-> Name
-> 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
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)
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)
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)
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
instance Produces ReplaceFlowSchema MimeJSON
instance Produces ReplaceFlowSchema MimeVndKubernetesProtobuf
instance Produces ReplaceFlowSchema MimeCbor
instance Produces ReplaceFlowSchema MimeYaml
replaceFlowSchemaStatus
:: (Consumes ReplaceFlowSchemaStatus contentType, MimeRender contentType V1FlowSchema)
=> ContentType contentType
-> Accept accept
-> V1FlowSchema
-> Name
-> 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
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)
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)
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)
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
instance Produces ReplaceFlowSchemaStatus MimeJSON
instance Produces ReplaceFlowSchemaStatus MimeVndKubernetesProtobuf
instance Produces ReplaceFlowSchemaStatus MimeCbor
instance Produces ReplaceFlowSchemaStatus MimeYaml
replacePriorityLevelConfiguration
:: (Consumes ReplacePriorityLevelConfiguration contentType, MimeRender contentType V1PriorityLevelConfiguration)
=> ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> Name
-> 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
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)
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)
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)
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
instance Produces ReplacePriorityLevelConfiguration MimeJSON
instance Produces ReplacePriorityLevelConfiguration MimeVndKubernetesProtobuf
instance Produces ReplacePriorityLevelConfiguration MimeCbor
instance Produces ReplacePriorityLevelConfiguration MimeYaml
replacePriorityLevelConfigurationStatus
:: (Consumes ReplacePriorityLevelConfigurationStatus contentType, MimeRender contentType V1PriorityLevelConfiguration)
=> ContentType contentType
-> Accept accept
-> V1PriorityLevelConfiguration
-> Name
-> 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
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)
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)
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)
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
instance Produces ReplacePriorityLevelConfigurationStatus MimeJSON
instance Produces ReplacePriorityLevelConfigurationStatus MimeVndKubernetesProtobuf
instance Produces ReplacePriorityLevelConfigurationStatus MimeCbor
instance Produces ReplacePriorityLevelConfigurationStatus MimeYaml