{-# 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.StorageV1beta1 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
createCSIDriver
:: (Consumes CreateCSIDriver contentType, MimeRender contentType V1beta1CSIDriver)
=> ContentType contentType
-> Accept accept
-> V1beta1CSIDriver
-> KubernetesRequest CreateCSIDriver contentType V1beta1CSIDriver accept
createCSIDriver :: ContentType contentType
-> Accept accept
-> V1beta1CSIDriver
-> KubernetesRequest
CreateCSIDriver contentType V1beta1CSIDriver accept
createCSIDriver ContentType contentType
_ Accept accept
_ V1beta1CSIDriver
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateCSIDriver contentType V1beta1CSIDriver accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers"]
KubernetesRequest
CreateCSIDriver contentType V1beta1CSIDriver accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateCSIDriver contentType V1beta1CSIDriver 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
CreateCSIDriver contentType V1beta1CSIDriver accept
-> V1beta1CSIDriver
-> KubernetesRequest
CreateCSIDriver contentType V1beta1CSIDriver accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1CSIDriver
body
data CreateCSIDriver
instance HasBodyParam CreateCSIDriver V1beta1CSIDriver
instance HasOptionalParam CreateCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept
-> Pretty
-> KubernetesRequest CreateCSIDriver contentType res accept
applyOptionalParam KubernetesRequest CreateCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateCSIDriver contentType res accept
req KubernetesRequest CreateCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateCSIDriver DryRun where
applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept
-> DryRun
-> KubernetesRequest CreateCSIDriver contentType res accept
applyOptionalParam KubernetesRequest CreateCSIDriver contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateCSIDriver contentType res accept
req KubernetesRequest CreateCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateCSIDriver FieldManager where
applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept
-> FieldManager
-> KubernetesRequest CreateCSIDriver contentType res accept
applyOptionalParam KubernetesRequest CreateCSIDriver contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateCSIDriver contentType res accept
req KubernetesRequest CreateCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateCSIDriver mtype
instance Produces CreateCSIDriver MimeJSON
instance Produces CreateCSIDriver MimeVndKubernetesProtobuf
instance Produces CreateCSIDriver MimeYaml
createCSINode
:: (Consumes CreateCSINode contentType, MimeRender contentType V1beta1CSINode)
=> ContentType contentType
-> Accept accept
-> V1beta1CSINode
-> KubernetesRequest CreateCSINode contentType V1beta1CSINode accept
createCSINode :: ContentType contentType
-> Accept accept
-> V1beta1CSINode
-> KubernetesRequest
CreateCSINode contentType V1beta1CSINode accept
createCSINode ContentType contentType
_ Accept accept
_ V1beta1CSINode
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateCSINode contentType V1beta1CSINode accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes"]
KubernetesRequest CreateCSINode contentType V1beta1CSINode accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateCSINode contentType V1beta1CSINode 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 CreateCSINode contentType V1beta1CSINode accept
-> V1beta1CSINode
-> KubernetesRequest
CreateCSINode contentType V1beta1CSINode accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1CSINode
body
data CreateCSINode
instance HasBodyParam CreateCSINode V1beta1CSINode
instance HasOptionalParam CreateCSINode Pretty where
applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept
-> Pretty -> KubernetesRequest CreateCSINode contentType res accept
applyOptionalParam KubernetesRequest CreateCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateCSINode contentType res accept
req KubernetesRequest CreateCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateCSINode DryRun where
applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept
-> DryRun -> KubernetesRequest CreateCSINode contentType res accept
applyOptionalParam KubernetesRequest CreateCSINode contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateCSINode contentType res accept
req KubernetesRequest CreateCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateCSINode FieldManager where
applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept
-> FieldManager
-> KubernetesRequest CreateCSINode contentType res accept
applyOptionalParam KubernetesRequest CreateCSINode contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateCSINode contentType res accept
req KubernetesRequest CreateCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateCSINode mtype
instance Produces CreateCSINode MimeJSON
instance Produces CreateCSINode MimeVndKubernetesProtobuf
instance Produces CreateCSINode MimeYaml
createStorageClass
:: (Consumes CreateStorageClass contentType, MimeRender contentType V1beta1StorageClass)
=> ContentType contentType
-> Accept accept
-> V1beta1StorageClass
-> KubernetesRequest CreateStorageClass contentType V1beta1StorageClass accept
createStorageClass :: ContentType contentType
-> Accept accept
-> V1beta1StorageClass
-> KubernetesRequest
CreateStorageClass contentType V1beta1StorageClass accept
createStorageClass ContentType contentType
_ Accept accept
_ V1beta1StorageClass
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateStorageClass contentType V1beta1StorageClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses"]
KubernetesRequest
CreateStorageClass contentType V1beta1StorageClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateStorageClass contentType V1beta1StorageClass 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
CreateStorageClass contentType V1beta1StorageClass accept
-> V1beta1StorageClass
-> KubernetesRequest
CreateStorageClass contentType V1beta1StorageClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1StorageClass
body
data CreateStorageClass
instance HasBodyParam CreateStorageClass V1beta1StorageClass
instance HasOptionalParam CreateStorageClass Pretty where
applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept
-> Pretty
-> KubernetesRequest CreateStorageClass contentType res accept
applyOptionalParam KubernetesRequest CreateStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateStorageClass contentType res accept
req KubernetesRequest CreateStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateStorageClass DryRun where
applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept
-> DryRun
-> KubernetesRequest CreateStorageClass contentType res accept
applyOptionalParam KubernetesRequest CreateStorageClass contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateStorageClass contentType res accept
req KubernetesRequest CreateStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateStorageClass FieldManager where
applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept
-> FieldManager
-> KubernetesRequest CreateStorageClass contentType res accept
applyOptionalParam KubernetesRequest CreateStorageClass contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateStorageClass contentType res accept
req KubernetesRequest CreateStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateStorageClass mtype
instance Produces CreateStorageClass MimeJSON
instance Produces CreateStorageClass MimeVndKubernetesProtobuf
instance Produces CreateStorageClass MimeYaml
createVolumeAttachment
:: (Consumes CreateVolumeAttachment contentType, MimeRender contentType V1beta1VolumeAttachment)
=> ContentType contentType
-> Accept accept
-> V1beta1VolumeAttachment
-> KubernetesRequest CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
createVolumeAttachment :: ContentType contentType
-> Accept accept
-> V1beta1VolumeAttachment
-> KubernetesRequest
CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
createVolumeAttachment ContentType contentType
_ Accept accept
_ V1beta1VolumeAttachment
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments"]
KubernetesRequest
CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateVolumeAttachment contentType V1beta1VolumeAttachment 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
CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
-> V1beta1VolumeAttachment
-> KubernetesRequest
CreateVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1VolumeAttachment
body
data CreateVolumeAttachment
instance HasBodyParam CreateVolumeAttachment V1beta1VolumeAttachment
instance HasOptionalParam CreateVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest CreateVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest CreateVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateVolumeAttachment contentType res accept
req KubernetesRequest CreateVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateVolumeAttachment DryRun where
applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept
-> DryRun
-> KubernetesRequest CreateVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest CreateVolumeAttachment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateVolumeAttachment contentType res accept
req KubernetesRequest CreateVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 CreateVolumeAttachment FieldManager where
applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept
-> FieldManager
-> KubernetesRequest CreateVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest CreateVolumeAttachment contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateVolumeAttachment contentType res accept
req KubernetesRequest CreateVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateVolumeAttachment mtype
instance Produces CreateVolumeAttachment MimeJSON
instance Produces CreateVolumeAttachment MimeVndKubernetesProtobuf
instance Produces CreateVolumeAttachment MimeYaml
deleteCSIDriver
:: (Consumes DeleteCSIDriver contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteCSIDriver contentType V1Status accept
deleteCSIDriver :: ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteCSIDriver contentType V1Status accept
deleteCSIDriver ContentType contentType
_ Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest DeleteCSIDriver contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest DeleteCSIDriver contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteCSIDriver 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 DeleteCSIDriver
instance HasBodyParam DeleteCSIDriver V1DeleteOptions
instance HasOptionalParam DeleteCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept
-> Pretty
-> KubernetesRequest DeleteCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteCSIDriver contentType res accept
req KubernetesRequest DeleteCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSIDriver DryRun where
applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept
-> DryRun
-> KubernetesRequest DeleteCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCSIDriver contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteCSIDriver contentType res accept
req KubernetesRequest DeleteCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSIDriver GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCSIDriver contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteCSIDriver contentType res accept
req KubernetesRequest DeleteCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSIDriver 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 DeleteCSIDriver OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCSIDriver contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteCSIDriver contentType res accept
req KubernetesRequest DeleteCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSIDriver 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 DeleteCSIDriver PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCSIDriver contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteCSIDriver contentType res accept
req KubernetesRequest DeleteCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSIDriver mtype
instance Produces DeleteCSIDriver MimeJSON
instance Produces DeleteCSIDriver MimeVndKubernetesProtobuf
instance Produces DeleteCSIDriver MimeYaml
deleteCSINode
:: (Consumes DeleteCSINode contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteCSINode contentType V1Status accept
deleteCSINode :: ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteCSINode contentType V1Status accept
deleteCSINode ContentType contentType
_ Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest DeleteCSINode contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest DeleteCSINode contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteCSINode 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 DeleteCSINode
instance HasBodyParam DeleteCSINode V1DeleteOptions
instance HasOptionalParam DeleteCSINode Pretty where
applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept
-> Pretty -> KubernetesRequest DeleteCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteCSINode contentType res accept
req KubernetesRequest DeleteCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSINode DryRun where
applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept
-> DryRun -> KubernetesRequest DeleteCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCSINode contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteCSINode contentType res accept
req KubernetesRequest DeleteCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSINode GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCSINode contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteCSINode contentType res accept
req KubernetesRequest DeleteCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSINode 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 DeleteCSINode OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCSINode contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteCSINode contentType res accept
req KubernetesRequest DeleteCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSINode 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 DeleteCSINode PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCSINode contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteCSINode contentType res accept
req KubernetesRequest DeleteCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCSINode mtype
instance Produces DeleteCSINode MimeJSON
instance Produces DeleteCSINode MimeVndKubernetesProtobuf
instance Produces DeleteCSINode MimeYaml
deleteCollectionCSIDriver
:: (Consumes DeleteCollectionCSIDriver contentType)
=> ContentType contentType
-> Accept accept
-> KubernetesRequest DeleteCollectionCSIDriver contentType V1Status accept
deleteCollectionCSIDriver :: ContentType contentType
-> Accept accept
-> KubernetesRequest
DeleteCollectionCSIDriver contentType V1Status accept
deleteCollectionCSIDriver ContentType contentType
_ Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers"]
KubernetesRequest
DeleteCollectionCSIDriver contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionCSIDriver 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 DeleteCollectionCSIDriver
instance HasBodyParam DeleteCollectionCSIDriver V1DeleteOptions
instance HasOptionalParam DeleteCollectionCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver Continue where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (Continue Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver DryRun where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver FieldSelector where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver 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 DeleteCollectionCSIDriver LabelSelector where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver Limit where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (Limit Int
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver 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 DeleteCollectionCSIDriver OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver 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 DeleteCollectionCSIDriver PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver ResourceVersion where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSIDriver TimeoutSeconds where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionCSIDriver contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest DeleteCollectionCSIDriver contentType res accept
req KubernetesRequest DeleteCollectionCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionCSIDriver 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 DeleteCollectionCSIDriver mtype
instance Produces DeleteCollectionCSIDriver MimeJSON
instance Produces DeleteCollectionCSIDriver MimeVndKubernetesProtobuf
instance Produces DeleteCollectionCSIDriver MimeYaml
deleteCollectionCSINode
:: (Consumes DeleteCollectionCSINode contentType)
=> ContentType contentType
-> Accept accept
-> KubernetesRequest DeleteCollectionCSINode contentType V1Status accept
deleteCollectionCSINode :: ContentType contentType
-> Accept accept
-> KubernetesRequest
DeleteCollectionCSINode contentType V1Status accept
deleteCollectionCSINode ContentType contentType
_ Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionCSINode contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes"]
KubernetesRequest
DeleteCollectionCSINode contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionCSINode 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 DeleteCollectionCSINode
instance HasBodyParam DeleteCollectionCSINode V1DeleteOptions
instance HasOptionalParam DeleteCollectionCSINode Pretty where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> Pretty
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode Continue where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> Continue
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (Continue Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode DryRun where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> DryRun
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode FieldSelector where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> FieldSelector
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode 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 DeleteCollectionCSINode LabelSelector where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> LabelSelector
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode Limit where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> Limit
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (Limit Int
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode 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 DeleteCollectionCSINode OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode 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 DeleteCollectionCSINode PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode ResourceVersion where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> ResourceVersion
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionCSINode TimeoutSeconds where
applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept
-> TimeoutSeconds
-> KubernetesRequest DeleteCollectionCSINode contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionCSINode contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest DeleteCollectionCSINode contentType res accept
req KubernetesRequest DeleteCollectionCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteCollectionCSINode 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 DeleteCollectionCSINode mtype
instance Produces DeleteCollectionCSINode MimeJSON
instance Produces DeleteCollectionCSINode MimeVndKubernetesProtobuf
instance Produces DeleteCollectionCSINode MimeYaml
deleteCollectionStorageClass
:: (Consumes DeleteCollectionStorageClass contentType)
=> ContentType contentType
-> Accept accept
-> KubernetesRequest DeleteCollectionStorageClass contentType V1Status accept
deleteCollectionStorageClass :: ContentType contentType
-> Accept accept
-> KubernetesRequest
DeleteCollectionStorageClass contentType V1Status accept
deleteCollectionStorageClass ContentType contentType
_ Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionStorageClass contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses"]
KubernetesRequest
DeleteCollectionStorageClass contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionStorageClass 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 DeleteCollectionStorageClass
instance HasBodyParam DeleteCollectionStorageClass V1DeleteOptions
instance HasOptionalParam DeleteCollectionStorageClass Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass 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 DeleteCollectionStorageClass LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass 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 DeleteCollectionStorageClass OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass 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 DeleteCollectionStorageClass PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionStorageClass TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionStorageClass contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionStorageClass contentType res accept
req KubernetesRequest
DeleteCollectionStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionStorageClass 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 DeleteCollectionStorageClass mtype
instance Produces DeleteCollectionStorageClass MimeJSON
instance Produces DeleteCollectionStorageClass MimeVndKubernetesProtobuf
instance Produces DeleteCollectionStorageClass MimeYaml
deleteCollectionVolumeAttachment
:: (Consumes DeleteCollectionVolumeAttachment contentType)
=> ContentType contentType
-> Accept accept
-> KubernetesRequest DeleteCollectionVolumeAttachment contentType V1Status accept
deleteCollectionVolumeAttachment :: ContentType contentType
-> Accept accept
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType V1Status accept
deleteCollectionVolumeAttachment ContentType contentType
_ Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments"]
KubernetesRequest
DeleteCollectionVolumeAttachment contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionVolumeAttachment 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 DeleteCollectionVolumeAttachment
instance HasBodyParam DeleteCollectionVolumeAttachment V1DeleteOptions
instance HasOptionalParam DeleteCollectionVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment 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 DeleteCollectionVolumeAttachment LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment 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 DeleteCollectionVolumeAttachment OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment 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 DeleteCollectionVolumeAttachment PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteCollectionVolumeAttachment TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
req KubernetesRequest
DeleteCollectionVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionVolumeAttachment 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 DeleteCollectionVolumeAttachment mtype
instance Produces DeleteCollectionVolumeAttachment MimeJSON
instance Produces DeleteCollectionVolumeAttachment MimeVndKubernetesProtobuf
instance Produces DeleteCollectionVolumeAttachment MimeYaml
deleteStorageClass
:: (Consumes DeleteStorageClass contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteStorageClass contentType V1Status accept
deleteStorageClass :: ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteStorageClass contentType V1Status accept
deleteStorageClass ContentType contentType
_ Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest DeleteStorageClass contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest DeleteStorageClass contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteStorageClass 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 DeleteStorageClass
instance HasBodyParam DeleteStorageClass V1DeleteOptions
instance HasOptionalParam DeleteStorageClass Pretty where
applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept
-> Pretty
-> KubernetesRequest DeleteStorageClass contentType res accept
applyOptionalParam KubernetesRequest DeleteStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteStorageClass contentType res accept
req KubernetesRequest DeleteStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteStorageClass DryRun where
applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept
-> DryRun
-> KubernetesRequest DeleteStorageClass contentType res accept
applyOptionalParam KubernetesRequest DeleteStorageClass contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteStorageClass contentType res accept
req KubernetesRequest DeleteStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteStorageClass GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteStorageClass contentType res accept
applyOptionalParam KubernetesRequest DeleteStorageClass contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteStorageClass contentType res accept
req KubernetesRequest DeleteStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteStorageClass 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 DeleteStorageClass OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteStorageClass contentType res accept
applyOptionalParam KubernetesRequest DeleteStorageClass contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteStorageClass contentType res accept
req KubernetesRequest DeleteStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteStorageClass 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 DeleteStorageClass PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteStorageClass contentType res accept
applyOptionalParam KubernetesRequest DeleteStorageClass contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteStorageClass contentType res accept
req KubernetesRequest DeleteStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteStorageClass mtype
instance Produces DeleteStorageClass MimeJSON
instance Produces DeleteStorageClass MimeVndKubernetesProtobuf
instance Produces DeleteStorageClass MimeYaml
deleteVolumeAttachment
:: (Consumes DeleteVolumeAttachment contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteVolumeAttachment contentType V1Status accept
deleteVolumeAttachment :: ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest
DeleteVolumeAttachment contentType V1Status accept
deleteVolumeAttachment ContentType contentType
_ Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteVolumeAttachment contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteVolumeAttachment contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteVolumeAttachment 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 DeleteVolumeAttachment
instance HasBodyParam DeleteVolumeAttachment V1DeleteOptions
instance HasOptionalParam DeleteVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest DeleteVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteVolumeAttachment contentType res accept
req KubernetesRequest DeleteVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteVolumeAttachment DryRun where
applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept
-> DryRun
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest DeleteVolumeAttachment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteVolumeAttachment contentType res accept
req KubernetesRequest DeleteVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteVolumeAttachment GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest DeleteVolumeAttachment contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteVolumeAttachment contentType res accept
req KubernetesRequest DeleteVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteVolumeAttachment 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 DeleteVolumeAttachment OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest DeleteVolumeAttachment contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteVolumeAttachment contentType res accept
req KubernetesRequest DeleteVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteVolumeAttachment 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 DeleteVolumeAttachment PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest DeleteVolumeAttachment contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteVolumeAttachment contentType res accept
req KubernetesRequest DeleteVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 DeleteVolumeAttachment mtype
instance Produces DeleteVolumeAttachment MimeJSON
instance Produces DeleteVolumeAttachment MimeVndKubernetesProtobuf
instance Produces DeleteVolumeAttachment MimeYaml
getAPIResources
:: Accept accept
-> KubernetesRequest GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources :: 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/storage.k8s.io/v1beta1/"]
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 MimeYaml
listCSIDriver
:: Accept accept
-> KubernetesRequest ListCSIDriver MimeNoContent V1beta1CSIDriverList accept
listCSIDriver :: Accept accept
-> KubernetesRequest
ListCSIDriver MimeNoContent V1beta1CSIDriverList accept
listCSIDriver Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListCSIDriver MimeNoContent V1beta1CSIDriverList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers"]
KubernetesRequest
ListCSIDriver MimeNoContent V1beta1CSIDriverList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListCSIDriver MimeNoContent V1beta1CSIDriverList 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 ListCSIDriver
instance HasOptionalParam ListCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> Pretty -> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSIDriver AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver 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 ListCSIDriver Continue where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> Continue
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSIDriver FieldSelector where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> FieldSelector
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSIDriver LabelSelector where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> LabelSelector
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSIDriver Limit where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> Limit -> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver 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 ListCSIDriver ResourceVersion where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> ResourceVersion
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSIDriver TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver 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 ListCSIDriver Watch where
applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept
-> Watch -> KubernetesRequest ListCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ListCSIDriver contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListCSIDriver contentType res accept
req KubernetesRequest ListCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSIDriver 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 ListCSIDriver MimeJSON
instance Produces ListCSIDriver MimeJsonstreamwatch
instance Produces ListCSIDriver MimeVndKubernetesProtobuf
instance Produces ListCSIDriver MimeVndKubernetesProtobufstreamwatch
instance Produces ListCSIDriver MimeYaml
listCSINode
:: Accept accept
-> KubernetesRequest ListCSINode MimeNoContent V1beta1CSINodeList accept
listCSINode :: Accept accept
-> KubernetesRequest
ListCSINode MimeNoContent V1beta1CSINodeList accept
listCSINode Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListCSINode MimeNoContent V1beta1CSINodeList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes"]
KubernetesRequest
ListCSINode MimeNoContent V1beta1CSINodeList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListCSINode MimeNoContent V1beta1CSINodeList 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 ListCSINode
instance HasOptionalParam ListCSINode Pretty where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> Pretty -> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSINode AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode 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 ListCSINode Continue where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> Continue -> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSINode FieldSelector where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> FieldSelector
-> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSINode LabelSelector where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> LabelSelector
-> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSINode Limit where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> Limit -> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode 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 ListCSINode ResourceVersion where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> ResourceVersion
-> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListCSINode TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode 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 ListCSINode Watch where
applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept
-> Watch -> KubernetesRequest ListCSINode contentType res accept
applyOptionalParam KubernetesRequest ListCSINode contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListCSINode contentType res accept
req KubernetesRequest ListCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ListCSINode 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 ListCSINode MimeJSON
instance Produces ListCSINode MimeJsonstreamwatch
instance Produces ListCSINode MimeVndKubernetesProtobuf
instance Produces ListCSINode MimeVndKubernetesProtobufstreamwatch
instance Produces ListCSINode MimeYaml
listStorageClass
:: Accept accept
-> KubernetesRequest ListStorageClass MimeNoContent V1beta1StorageClassList accept
listStorageClass :: Accept accept
-> KubernetesRequest
ListStorageClass MimeNoContent V1beta1StorageClassList accept
listStorageClass Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListStorageClass MimeNoContent V1beta1StorageClassList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses"]
KubernetesRequest
ListStorageClass MimeNoContent V1beta1StorageClassList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListStorageClass MimeNoContent V1beta1StorageClassList 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 ListStorageClass
instance HasOptionalParam ListStorageClass Pretty where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> Pretty
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListStorageClass AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass 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 ListStorageClass Continue where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> Continue
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListStorageClass FieldSelector where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> FieldSelector
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListStorageClass LabelSelector where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> LabelSelector
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListStorageClass Limit where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> Limit
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass 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 ListStorageClass ResourceVersion where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> ResourceVersion
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListStorageClass TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass 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 ListStorageClass Watch where
applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept
-> Watch
-> KubernetesRequest ListStorageClass contentType res accept
applyOptionalParam KubernetesRequest ListStorageClass contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListStorageClass contentType res accept
req KubernetesRequest ListStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ListStorageClass 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 ListStorageClass MimeJSON
instance Produces ListStorageClass MimeJsonstreamwatch
instance Produces ListStorageClass MimeVndKubernetesProtobuf
instance Produces ListStorageClass MimeVndKubernetesProtobufstreamwatch
instance Produces ListStorageClass MimeYaml
listVolumeAttachment
:: Accept accept
-> KubernetesRequest ListVolumeAttachment MimeNoContent V1beta1VolumeAttachmentList accept
listVolumeAttachment :: Accept accept
-> KubernetesRequest
ListVolumeAttachment
MimeNoContent
V1beta1VolumeAttachmentList
accept
listVolumeAttachment Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListVolumeAttachment
MimeNoContent
V1beta1VolumeAttachmentList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments"]
KubernetesRequest
ListVolumeAttachment
MimeNoContent
V1beta1VolumeAttachmentList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListVolumeAttachment
MimeNoContent
V1beta1VolumeAttachmentList
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 ListVolumeAttachment
instance HasOptionalParam ListVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListVolumeAttachment AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment 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 ListVolumeAttachment Continue where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> Continue
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListVolumeAttachment FieldSelector where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> FieldSelector
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListVolumeAttachment LabelSelector where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> LabelSelector
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListVolumeAttachment Limit where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> Limit
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment 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 ListVolumeAttachment ResourceVersion where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> ResourceVersion
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ListVolumeAttachment TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment 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 ListVolumeAttachment Watch where
applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept
-> Watch
-> KubernetesRequest ListVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ListVolumeAttachment contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListVolumeAttachment contentType res accept
req KubernetesRequest ListVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ListVolumeAttachment 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 ListVolumeAttachment MimeJSON
instance Produces ListVolumeAttachment MimeJsonstreamwatch
instance Produces ListVolumeAttachment MimeVndKubernetesProtobuf
instance Produces ListVolumeAttachment MimeVndKubernetesProtobufstreamwatch
instance Produces ListVolumeAttachment MimeYaml
patchCSIDriver
:: (Consumes PatchCSIDriver contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchCSIDriver contentType V1beta1CSIDriver accept
patchCSIDriver :: ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
PatchCSIDriver contentType V1beta1CSIDriver accept
patchCSIDriver ContentType contentType
_ Accept accept
_ Body
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchCSIDriver contentType V1beta1CSIDriver accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
PatchCSIDriver contentType V1beta1CSIDriver accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchCSIDriver contentType V1beta1CSIDriver 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
PatchCSIDriver contentType V1beta1CSIDriver accept
-> Body
-> KubernetesRequest
PatchCSIDriver contentType V1beta1CSIDriver accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` Body
body
data PatchCSIDriver
instance HasBodyParam PatchCSIDriver Body
instance HasOptionalParam PatchCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept
-> Pretty
-> KubernetesRequest PatchCSIDriver contentType res accept
applyOptionalParam KubernetesRequest PatchCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest PatchCSIDriver contentType res accept
req KubernetesRequest PatchCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSIDriver DryRun where
applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept
-> DryRun
-> KubernetesRequest PatchCSIDriver contentType res accept
applyOptionalParam KubernetesRequest PatchCSIDriver contentType res accept
req (DryRun Text
xs) =
KubernetesRequest PatchCSIDriver contentType res accept
req KubernetesRequest PatchCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSIDriver FieldManager where
applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept
-> FieldManager
-> KubernetesRequest PatchCSIDriver contentType res accept
applyOptionalParam KubernetesRequest PatchCSIDriver contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest PatchCSIDriver contentType res accept
req KubernetesRequest PatchCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSIDriver Force where
applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept
-> Force -> KubernetesRequest PatchCSIDriver contentType res accept
applyOptionalParam KubernetesRequest PatchCSIDriver contentType res accept
req (Force Bool
xs) =
KubernetesRequest PatchCSIDriver contentType res accept
req KubernetesRequest PatchCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSIDriver 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 PatchCSIDriver MimeApplyPatchyaml
instance Consumes PatchCSIDriver MimeJsonPatchjson
instance Consumes PatchCSIDriver MimeMergePatchjson
instance Consumes PatchCSIDriver MimeStrategicMergePatchjson
instance Produces PatchCSIDriver MimeJSON
instance Produces PatchCSIDriver MimeVndKubernetesProtobuf
instance Produces PatchCSIDriver MimeYaml
patchCSINode
:: (Consumes PatchCSINode contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchCSINode contentType V1beta1CSINode accept
patchCSINode :: ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchCSINode contentType V1beta1CSINode accept
patchCSINode ContentType contentType
_ Accept accept
_ Body
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest PatchCSINode contentType V1beta1CSINode accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest PatchCSINode contentType V1beta1CSINode accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest PatchCSINode contentType V1beta1CSINode 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 PatchCSINode contentType V1beta1CSINode accept
-> Body
-> KubernetesRequest PatchCSINode contentType V1beta1CSINode accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` Body
body
data PatchCSINode
instance HasBodyParam PatchCSINode Body
instance HasOptionalParam PatchCSINode Pretty where
applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept
-> Pretty -> KubernetesRequest PatchCSINode contentType res accept
applyOptionalParam KubernetesRequest PatchCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest PatchCSINode contentType res accept
req KubernetesRequest PatchCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSINode DryRun where
applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept
-> DryRun -> KubernetesRequest PatchCSINode contentType res accept
applyOptionalParam KubernetesRequest PatchCSINode contentType res accept
req (DryRun Text
xs) =
KubernetesRequest PatchCSINode contentType res accept
req KubernetesRequest PatchCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSINode FieldManager where
applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept
-> FieldManager
-> KubernetesRequest PatchCSINode contentType res accept
applyOptionalParam KubernetesRequest PatchCSINode contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest PatchCSINode contentType res accept
req KubernetesRequest PatchCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchCSINode Force where
applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept
-> Force -> KubernetesRequest PatchCSINode contentType res accept
applyOptionalParam KubernetesRequest PatchCSINode contentType res accept
req (Force Bool
xs) =
KubernetesRequest PatchCSINode contentType res accept
req KubernetesRequest PatchCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchCSINode 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 PatchCSINode MimeApplyPatchyaml
instance Consumes PatchCSINode MimeJsonPatchjson
instance Consumes PatchCSINode MimeMergePatchjson
instance Consumes PatchCSINode MimeStrategicMergePatchjson
instance Produces PatchCSINode MimeJSON
instance Produces PatchCSINode MimeVndKubernetesProtobuf
instance Produces PatchCSINode MimeYaml
patchStorageClass
:: (Consumes PatchStorageClass contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchStorageClass contentType V1beta1StorageClass accept
patchStorageClass :: ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
PatchStorageClass contentType V1beta1StorageClass accept
patchStorageClass ContentType contentType
_ Accept accept
_ Body
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchStorageClass contentType V1beta1StorageClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
PatchStorageClass contentType V1beta1StorageClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchStorageClass contentType V1beta1StorageClass 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
PatchStorageClass contentType V1beta1StorageClass accept
-> Body
-> KubernetesRequest
PatchStorageClass contentType V1beta1StorageClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` Body
body
data PatchStorageClass
instance HasBodyParam PatchStorageClass Body
instance HasOptionalParam PatchStorageClass Pretty where
applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept
-> Pretty
-> KubernetesRequest PatchStorageClass contentType res accept
applyOptionalParam KubernetesRequest PatchStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest PatchStorageClass contentType res accept
req KubernetesRequest PatchStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchStorageClass DryRun where
applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept
-> DryRun
-> KubernetesRequest PatchStorageClass contentType res accept
applyOptionalParam KubernetesRequest PatchStorageClass contentType res accept
req (DryRun Text
xs) =
KubernetesRequest PatchStorageClass contentType res accept
req KubernetesRequest PatchStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchStorageClass FieldManager where
applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept
-> FieldManager
-> KubernetesRequest PatchStorageClass contentType res accept
applyOptionalParam KubernetesRequest PatchStorageClass contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest PatchStorageClass contentType res accept
req KubernetesRequest PatchStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchStorageClass Force where
applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept
-> Force
-> KubernetesRequest PatchStorageClass contentType res accept
applyOptionalParam KubernetesRequest PatchStorageClass contentType res accept
req (Force Bool
xs) =
KubernetesRequest PatchStorageClass contentType res accept
req KubernetesRequest PatchStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchStorageClass 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 PatchStorageClass MimeApplyPatchyaml
instance Consumes PatchStorageClass MimeJsonPatchjson
instance Consumes PatchStorageClass MimeMergePatchjson
instance Consumes PatchStorageClass MimeStrategicMergePatchjson
instance Produces PatchStorageClass MimeJSON
instance Produces PatchStorageClass MimeVndKubernetesProtobuf
instance Produces PatchStorageClass MimeYaml
patchVolumeAttachment
:: (Consumes PatchVolumeAttachment contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
patchVolumeAttachment :: ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
patchVolumeAttachment ContentType contentType
_ Accept accept
_ Body
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchVolumeAttachment contentType V1beta1VolumeAttachment 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
PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
-> Body
-> KubernetesRequest
PatchVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` Body
body
data PatchVolumeAttachment
instance HasBodyParam PatchVolumeAttachment Body
instance HasOptionalParam PatchVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest PatchVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest PatchVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest PatchVolumeAttachment contentType res accept
req KubernetesRequest PatchVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchVolumeAttachment DryRun where
applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept
-> DryRun
-> KubernetesRequest PatchVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest PatchVolumeAttachment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest PatchVolumeAttachment contentType res accept
req KubernetesRequest PatchVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchVolumeAttachment FieldManager where
applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept
-> FieldManager
-> KubernetesRequest PatchVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest PatchVolumeAttachment contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest PatchVolumeAttachment contentType res accept
req KubernetesRequest PatchVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 PatchVolumeAttachment Force where
applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept
-> Force
-> KubernetesRequest PatchVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest PatchVolumeAttachment contentType res accept
req (Force Bool
xs) =
KubernetesRequest PatchVolumeAttachment contentType res accept
req KubernetesRequest PatchVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchVolumeAttachment 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 PatchVolumeAttachment MimeApplyPatchyaml
instance Consumes PatchVolumeAttachment MimeJsonPatchjson
instance Consumes PatchVolumeAttachment MimeMergePatchjson
instance Consumes PatchVolumeAttachment MimeStrategicMergePatchjson
instance Produces PatchVolumeAttachment MimeJSON
instance Produces PatchVolumeAttachment MimeVndKubernetesProtobuf
instance Produces PatchVolumeAttachment MimeYaml
readCSIDriver
:: Accept accept
-> Name
-> KubernetesRequest ReadCSIDriver MimeNoContent V1beta1CSIDriver accept
readCSIDriver :: Accept accept
-> Name
-> KubernetesRequest
ReadCSIDriver MimeNoContent V1beta1CSIDriver accept
readCSIDriver Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReadCSIDriver MimeNoContent V1beta1CSIDriver accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReadCSIDriver MimeNoContent V1beta1CSIDriver accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReadCSIDriver MimeNoContent V1beta1CSIDriver 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 ReadCSIDriver
instance HasOptionalParam ReadCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept
-> Pretty -> KubernetesRequest ReadCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReadCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReadCSIDriver contentType res accept
req KubernetesRequest ReadCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReadCSIDriver Exact where
applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept
-> Exact -> KubernetesRequest ReadCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReadCSIDriver contentType res accept
req (Exact Bool
xs) =
KubernetesRequest ReadCSIDriver contentType res accept
req KubernetesRequest ReadCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSIDriver 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
"exact", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ReadCSIDriver Export where
applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept
-> Export -> KubernetesRequest ReadCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReadCSIDriver contentType res accept
req (Export Bool
xs) =
KubernetesRequest ReadCSIDriver contentType res accept
req KubernetesRequest ReadCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSIDriver 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
"export", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ReadCSIDriver MimeJSON
instance Produces ReadCSIDriver MimeVndKubernetesProtobuf
instance Produces ReadCSIDriver MimeYaml
readCSINode
:: Accept accept
-> Name
-> KubernetesRequest ReadCSINode MimeNoContent V1beta1CSINode accept
readCSINode :: Accept accept
-> Name
-> KubernetesRequest
ReadCSINode MimeNoContent V1beta1CSINode accept
readCSINode Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReadCSINode MimeNoContent V1beta1CSINode accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest ReadCSINode MimeNoContent V1beta1CSINode accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReadCSINode MimeNoContent V1beta1CSINode 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 ReadCSINode
instance HasOptionalParam ReadCSINode Pretty where
applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept
-> Pretty -> KubernetesRequest ReadCSINode contentType res accept
applyOptionalParam KubernetesRequest ReadCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReadCSINode contentType res accept
req KubernetesRequest ReadCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReadCSINode Exact where
applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept
-> Exact -> KubernetesRequest ReadCSINode contentType res accept
applyOptionalParam KubernetesRequest ReadCSINode contentType res accept
req (Exact Bool
xs) =
KubernetesRequest ReadCSINode contentType res accept
req KubernetesRequest ReadCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSINode 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
"exact", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ReadCSINode Export where
applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept
-> Export -> KubernetesRequest ReadCSINode contentType res accept
applyOptionalParam KubernetesRequest ReadCSINode contentType res accept
req (Export Bool
xs) =
KubernetesRequest ReadCSINode contentType res accept
req KubernetesRequest ReadCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadCSINode 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
"export", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ReadCSINode MimeJSON
instance Produces ReadCSINode MimeVndKubernetesProtobuf
instance Produces ReadCSINode MimeYaml
readStorageClass
:: Accept accept
-> Name
-> KubernetesRequest ReadStorageClass MimeNoContent V1beta1StorageClass accept
readStorageClass :: Accept accept
-> Name
-> KubernetesRequest
ReadStorageClass MimeNoContent V1beta1StorageClass accept
readStorageClass Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReadStorageClass MimeNoContent V1beta1StorageClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReadStorageClass MimeNoContent V1beta1StorageClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReadStorageClass MimeNoContent V1beta1StorageClass 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 ReadStorageClass
instance HasOptionalParam ReadStorageClass Pretty where
applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept
-> Pretty
-> KubernetesRequest ReadStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReadStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReadStorageClass contentType res accept
req KubernetesRequest ReadStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReadStorageClass Exact where
applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept
-> Exact
-> KubernetesRequest ReadStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReadStorageClass contentType res accept
req (Exact Bool
xs) =
KubernetesRequest ReadStorageClass contentType res accept
req KubernetesRequest ReadStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadStorageClass 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
"exact", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ReadStorageClass Export where
applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept
-> Export
-> KubernetesRequest ReadStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReadStorageClass contentType res accept
req (Export Bool
xs) =
KubernetesRequest ReadStorageClass contentType res accept
req KubernetesRequest ReadStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadStorageClass 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
"export", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ReadStorageClass MimeJSON
instance Produces ReadStorageClass MimeVndKubernetesProtobuf
instance Produces ReadStorageClass MimeYaml
readVolumeAttachment
:: Accept accept
-> Name
-> KubernetesRequest ReadVolumeAttachment MimeNoContent V1beta1VolumeAttachment accept
readVolumeAttachment :: Accept accept
-> Name
-> KubernetesRequest
ReadVolumeAttachment MimeNoContent V1beta1VolumeAttachment accept
readVolumeAttachment Accept accept
_ (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReadVolumeAttachment MimeNoContent V1beta1VolumeAttachment accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReadVolumeAttachment MimeNoContent V1beta1VolumeAttachment accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReadVolumeAttachment MimeNoContent V1beta1VolumeAttachment 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 ReadVolumeAttachment
instance HasOptionalParam ReadVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest ReadVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReadVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReadVolumeAttachment contentType res accept
req KubernetesRequest ReadVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReadVolumeAttachment Exact where
applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept
-> Exact
-> KubernetesRequest ReadVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReadVolumeAttachment contentType res accept
req (Exact Bool
xs) =
KubernetesRequest ReadVolumeAttachment contentType res accept
req KubernetesRequest ReadVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadVolumeAttachment 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
"exact", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ReadVolumeAttachment Export where
applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept
-> Export
-> KubernetesRequest ReadVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReadVolumeAttachment contentType res accept
req (Export Bool
xs) =
KubernetesRequest ReadVolumeAttachment contentType res accept
req KubernetesRequest ReadVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadVolumeAttachment 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
"export", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ReadVolumeAttachment MimeJSON
instance Produces ReadVolumeAttachment MimeVndKubernetesProtobuf
instance Produces ReadVolumeAttachment MimeYaml
replaceCSIDriver
:: (Consumes ReplaceCSIDriver contentType, MimeRender contentType V1beta1CSIDriver)
=> ContentType contentType
-> Accept accept
-> V1beta1CSIDriver
-> Name
-> KubernetesRequest ReplaceCSIDriver contentType V1beta1CSIDriver accept
replaceCSIDriver :: ContentType contentType
-> Accept accept
-> V1beta1CSIDriver
-> Name
-> KubernetesRequest
ReplaceCSIDriver contentType V1beta1CSIDriver accept
replaceCSIDriver ContentType contentType
_ Accept accept
_ V1beta1CSIDriver
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceCSIDriver contentType V1beta1CSIDriver accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/storage.k8s.io/v1beta1/csidrivers/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReplaceCSIDriver contentType V1beta1CSIDriver accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceCSIDriver contentType V1beta1CSIDriver 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
ReplaceCSIDriver contentType V1beta1CSIDriver accept
-> V1beta1CSIDriver
-> KubernetesRequest
ReplaceCSIDriver contentType V1beta1CSIDriver accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1CSIDriver
body
data ReplaceCSIDriver
instance HasBodyParam ReplaceCSIDriver V1beta1CSIDriver
instance HasOptionalParam ReplaceCSIDriver Pretty where
applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept
-> Pretty
-> KubernetesRequest ReplaceCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSIDriver contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReplaceCSIDriver contentType res accept
req KubernetesRequest ReplaceCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceCSIDriver DryRun where
applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept
-> DryRun
-> KubernetesRequest ReplaceCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSIDriver contentType res accept
req (DryRun Text
xs) =
KubernetesRequest ReplaceCSIDriver contentType res accept
req KubernetesRequest ReplaceCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceCSIDriver FieldManager where
applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceCSIDriver contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSIDriver contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest ReplaceCSIDriver contentType res accept
req KubernetesRequest ReplaceCSIDriver contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSIDriver contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes ReplaceCSIDriver mtype
instance Produces ReplaceCSIDriver MimeJSON
instance Produces ReplaceCSIDriver MimeVndKubernetesProtobuf
instance Produces ReplaceCSIDriver MimeYaml
replaceCSINode
:: (Consumes ReplaceCSINode contentType, MimeRender contentType V1beta1CSINode)
=> ContentType contentType
-> Accept accept
-> V1beta1CSINode
-> Name
-> KubernetesRequest ReplaceCSINode contentType V1beta1CSINode accept
replaceCSINode :: ContentType contentType
-> Accept accept
-> V1beta1CSINode
-> Name
-> KubernetesRequest
ReplaceCSINode contentType V1beta1CSINode accept
replaceCSINode ContentType contentType
_ Accept accept
_ V1beta1CSINode
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceCSINode contentType V1beta1CSINode accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/storage.k8s.io/v1beta1/csinodes/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest ReplaceCSINode contentType V1beta1CSINode accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceCSINode contentType V1beta1CSINode 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 ReplaceCSINode contentType V1beta1CSINode accept
-> V1beta1CSINode
-> KubernetesRequest
ReplaceCSINode contentType V1beta1CSINode accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1CSINode
body
data ReplaceCSINode
instance HasBodyParam ReplaceCSINode V1beta1CSINode
instance HasOptionalParam ReplaceCSINode Pretty where
applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept
-> Pretty
-> KubernetesRequest ReplaceCSINode contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSINode contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReplaceCSINode contentType res accept
req KubernetesRequest ReplaceCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceCSINode DryRun where
applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept
-> DryRun
-> KubernetesRequest ReplaceCSINode contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSINode contentType res accept
req (DryRun Text
xs) =
KubernetesRequest ReplaceCSINode contentType res accept
req KubernetesRequest ReplaceCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceCSINode FieldManager where
applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceCSINode contentType res accept
applyOptionalParam KubernetesRequest ReplaceCSINode contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest ReplaceCSINode contentType res accept
req KubernetesRequest ReplaceCSINode contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceCSINode contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes ReplaceCSINode mtype
instance Produces ReplaceCSINode MimeJSON
instance Produces ReplaceCSINode MimeVndKubernetesProtobuf
instance Produces ReplaceCSINode MimeYaml
replaceStorageClass
:: (Consumes ReplaceStorageClass contentType, MimeRender contentType V1beta1StorageClass)
=> ContentType contentType
-> Accept accept
-> V1beta1StorageClass
-> Name
-> KubernetesRequest ReplaceStorageClass contentType V1beta1StorageClass accept
replaceStorageClass :: ContentType contentType
-> Accept accept
-> V1beta1StorageClass
-> Name
-> KubernetesRequest
ReplaceStorageClass contentType V1beta1StorageClass accept
replaceStorageClass ContentType contentType
_ Accept accept
_ V1beta1StorageClass
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceStorageClass contentType V1beta1StorageClass accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/storage.k8s.io/v1beta1/storageclasses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReplaceStorageClass contentType V1beta1StorageClass accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceStorageClass contentType V1beta1StorageClass 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
ReplaceStorageClass contentType V1beta1StorageClass accept
-> V1beta1StorageClass
-> KubernetesRequest
ReplaceStorageClass contentType V1beta1StorageClass accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1StorageClass
body
data ReplaceStorageClass
instance HasBodyParam ReplaceStorageClass V1beta1StorageClass
instance HasOptionalParam ReplaceStorageClass Pretty where
applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept
-> Pretty
-> KubernetesRequest ReplaceStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceStorageClass contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReplaceStorageClass contentType res accept
req KubernetesRequest ReplaceStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceStorageClass DryRun where
applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept
-> DryRun
-> KubernetesRequest ReplaceStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceStorageClass contentType res accept
req (DryRun Text
xs) =
KubernetesRequest ReplaceStorageClass contentType res accept
req KubernetesRequest ReplaceStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceStorageClass FieldManager where
applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceStorageClass contentType res accept
applyOptionalParam KubernetesRequest ReplaceStorageClass contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest ReplaceStorageClass contentType res accept
req KubernetesRequest ReplaceStorageClass contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceStorageClass contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes ReplaceStorageClass mtype
instance Produces ReplaceStorageClass MimeJSON
instance Produces ReplaceStorageClass MimeVndKubernetesProtobuf
instance Produces ReplaceStorageClass MimeYaml
replaceVolumeAttachment
:: (Consumes ReplaceVolumeAttachment contentType, MimeRender contentType V1beta1VolumeAttachment)
=> ContentType contentType
-> Accept accept
-> V1beta1VolumeAttachment
-> Name
-> KubernetesRequest ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
replaceVolumeAttachment :: ContentType contentType
-> Accept accept
-> V1beta1VolumeAttachment
-> Name
-> KubernetesRequest
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
replaceVolumeAttachment ContentType contentType
_ Accept accept
_ V1beta1VolumeAttachment
body (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/storage.k8s.io/v1beta1/volumeattachments/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment 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
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
-> V1beta1VolumeAttachment
-> KubernetesRequest
ReplaceVolumeAttachment contentType V1beta1VolumeAttachment accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1beta1VolumeAttachment
body
data ReplaceVolumeAttachment
instance HasBodyParam ReplaceVolumeAttachment V1beta1VolumeAttachment
instance HasOptionalParam ReplaceVolumeAttachment Pretty where
applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> Pretty
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReplaceVolumeAttachment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ReplaceVolumeAttachment contentType res accept
req KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceVolumeAttachment DryRun where
applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> DryRun
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReplaceVolumeAttachment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest ReplaceVolumeAttachment contentType res accept
req KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req 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 ReplaceVolumeAttachment FieldManager where
applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
applyOptionalParam KubernetesRequest ReplaceVolumeAttachment contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest ReplaceVolumeAttachment contentType res accept
req KubernetesRequest ReplaceVolumeAttachment contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceVolumeAttachment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes ReplaceVolumeAttachment mtype
instance Produces ReplaceVolumeAttachment MimeJSON
instance Produces ReplaceVolumeAttachment MimeVndKubernetesProtobuf
instance Produces ReplaceVolumeAttachment MimeYaml